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.haskel