[commit: ghc] wip/nfs-locking: Use matchVersionedFilePath in registerPackage build rule. (f0f4193)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:51:07 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/f0f4193049fabd48cd1c0b5e37849319849b9bf5/ghc
>---------------------------------------------------------------
commit f0f4193049fabd48cd1c0b5e37849319849b9bf5
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Tue Feb 16 19:16:33 2016 +0000
Use matchVersionedFilePath in registerPackage build rule.
See #207.
>---------------------------------------------------------------
f0f4193049fabd48cd1c0b5e37849319849b9bf5
src/Rules/Register.hs | 9 ++-------
1 file changed, 2 insertions(+), 7 deletions(-)
diff --git a/src/Rules/Register.hs b/src/Rules/Register.hs
index 01d8ab9..85fac80 100644
--- a/src/Rules/Register.hs
+++ b/src/Rules/Register.hs
@@ -1,8 +1,6 @@
{-# LANGUAGE RecordWildCards #-}
module Rules.Register (registerPackage) where
-import Data.Char
-
import Base
import Context
import Expression
@@ -18,12 +16,9 @@ registerPackage :: [(Resource, Int)] -> Context -> Rules ()
registerPackage rs context @ (Context {..}) = do
let oldPath = pkgPath package -/- targetDirectory stage package -- TODO: remove, #113
pkgConf = packageDbDirectory stage -/- pkgNameString package
- match f = case stripPrefix (pkgConf ++ "-") f of
- Nothing -> False
- Just suf -> dropWhile (\c -> isDigit c || c == '.') suf == "conf"
- when (stage <= Stage1) $ match ?> \conf -> do
- -- This produces pkgConfig. TODO: Add explicit tracking
+ when (stage <= Stage1) $ matchVersionedFilePath pkgConf "conf" ?> \conf -> do
+ -- This produces inplace-pkg-config. TODO: Add explicit tracking
need [pkgDataFile stage package]
-- Post-process inplace-pkg-config. TODO: remove, see #113, #148
More information about the ghc-commits
mailing list