[commit: ghc] wip/nfs-locking: Add more utilities including install and symbolic link (#316) (8299d14)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 01:18:51 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/8299d146c112c16c528b3681a6e4404eb47c6375/ghc

>---------------------------------------------------------------

commit 8299d146c112c16c528b3681a6e4404eb47c6375
Author: Zhen Zhang <izgzhen at gmail.com>
Date:   Tue Jun 6 08:53:14 2017 +0800

    Add more utilities including install and symbolic link (#316)


>---------------------------------------------------------------

8299d146c112c16c528b3681a6e4404eb47c6375
 cfg/system.config.in          | 15 +++++++++++++
 src/Oracles/Config/Setting.hs | 50 ++++++++++++++++++++++++++++++++++++++++++-
 src/Util.hs                   | 44 ++++++++++++++++++++++++++++++++++++-
 3 files changed, 107 insertions(+), 2 deletions(-)

diff --git a/cfg/system.config.in b/cfg/system.config.in
index 667a22d..56a7c7f 100644
--- a/cfg/system.config.in
+++ b/cfg/system.config.in
@@ -22,6 +22,7 @@ system-ghc-pkg = @GhcPkgCmd@
 tar            = @TarCmd@
 patch          = @PatchCmd@
 perl           = @PerlCmd@
+ln-s           = @LN_S@
 
 # Information about builders:
 #============================
@@ -117,3 +118,17 @@ ffi-lib-dir       = @FFILibDir@
 #=======================
 
 with-libdw = @UseLibdw@
+
+# Installation:
+#=======================
+
+install-prefix          = @prefix@
+install-bindir          = @prefix@/bin
+install-libdir          = @prefix@/lib
+install-datarootdir     = @prefix@/share
+
+install         = @INSTALL@
+install-program = @INSTALL@ -m 755
+install-script  = @INSTALL@ -m 755
+install-data    = @INSTALL@ -m 644
+install-dir     = @INSTALL@ -m 755 -d
diff --git a/src/Oracles/Config/Setting.hs b/src/Oracles/Config/Setting.hs
index 0b28112..8bdc387 100644
--- a/src/Oracles/Config/Setting.hs
+++ b/src/Oracles/Config/Setting.hs
@@ -2,7 +2,8 @@ module Oracles.Config.Setting (
     Setting (..), SettingList (..), setting, settingList, getSetting,
     getSettingList, anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs,
     ghcWithInterpreter, ghcEnableTablesNextToCode, useLibFFIForAdjustors,
-    ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost
+    ghcCanonVersion, cmdLineLengthLimit, iosHost, osxHost, windowsHost,
+    relocatableBuild, installDocDir, installGhcLibDir
     ) where
 
 import Control.Monad.Trans.Reader
@@ -51,6 +52,19 @@ data Setting = BuildArch
              | GmpLibDir
              | IconvIncludeDir
              | IconvLibDir
+             -- Paths to where GHC is installed
+             | InstallPrefix
+             | InstallBinDir
+             | InstallLibDir
+             | InstallDataRootDir
+             -- "install" utility
+             | Install
+             | InstallData
+             | InstallProgram
+             | InstallScript
+             | InstallDir
+             -- symbolic link
+             | LnS
 
 data SettingList = ConfCcArgs Stage
                  | ConfCppArgs Stage
@@ -94,6 +108,16 @@ setting key = unsafeAskConfig $ case key of
     GmpLibDir          -> "gmp-lib-dir"
     IconvIncludeDir    -> "iconv-include-dir"
     IconvLibDir        -> "iconv-lib-dir"
+    InstallPrefix      -> "install-prefix"
+    InstallBinDir      -> "install-bindir"
+    InstallLibDir      -> "install-libdir"
+    InstallDataRootDir -> "install-datarootdir"
+    Install            -> "install"
+    InstallDir         -> "install-dir"
+    InstallProgram     -> "install-program"
+    InstallScript      -> "install-script"
+    InstallData        -> "install-data"
+    LnS                -> "ln-s"
 
 settingList :: SettingList -> Action [String]
 settingList key = fmap words $ unsafeAskConfig $ case key of
@@ -173,3 +197,27 @@ cmdLineLengthLimit = do
         (False, True) -> 200000
         -- On all other systems, we try this:
         _             -> 4194304 -- Cabal library needs a bit more than 2MB!
+
+-- | On Windows we normally want to make a relocatable bindist,
+-- to we ignore flags like libdir
+-- ref: mk/config.mk.in:232
+relocatableBuild :: Action Bool
+relocatableBuild = windowsHost
+
+installDocDir :: Action String
+installDocDir = do
+  version <- setting ProjectVersion
+  (-/- ("doc/ghc-" ++ version)) <$> setting InstallDataRootDir
+
+-- | Unix: override libdir and datadir to put ghc-specific stuff in
+-- a subdirectory with the version number included.
+-- ref: mk/install.mk:101
+-- TODO: CroosCompilePrefix
+installGhcLibDir :: Action String
+installGhcLibDir = do
+  r <- relocatableBuild
+  libdir <- setting InstallLibDir
+  if r then return libdir
+       else do
+         v <- setting ProjectVersion
+         return (libdir -/- ("ghc-" ++ v))
diff --git a/src/Util.hs b/src/Util.hs
index 1fd19f8..a7310be 100644
--- a/src/Util.hs
+++ b/src/Util.hs
@@ -3,7 +3,8 @@ module Util (
     removeFile, copyDirectory, copyDirectoryContents, createDirectory,
     moveDirectory, removeDirectory, applyPatch, runBuilder, runBuilderWith,
     makeExecutable, renderProgram, renderLibrary, Match(..), builderEnvironment,
-    needBuilder, copyFileUntracked
+    needBuilder, copyFileUntracked, installDir, installData, installScript,
+    installProgram, linkSymbolic
     ) where
 
 import qualified System.Directory.Extra as IO
@@ -18,6 +19,7 @@ import GHC
 import Oracles.ArgsHash
 import Oracles.DirectoryContents
 import Oracles.Path
+import Oracles.Config.Setting
 import Settings
 import Settings.Builders.Ar
 import Target
@@ -169,6 +171,46 @@ applyPatch dir patch = do
     putBuild $ "| Apply patch " ++ file
     quietly $ cmd Shell cmdEcho [Cwd dir] [path, "-p0 <", patch]
 
+-- | Install a directory
+installDir :: FilePath -> Action ()
+installDir dir = do
+    i <- setting InstallDir
+    putBuild $ "| Install directory" ++ dir
+    quietly $ cmd i dir
+
+-- | Install data file to a directory
+installData :: [FilePath] -> FilePath -> Action ()
+installData fs dir = do
+    i <- setting InstallData
+    forM_ fs $ \f ->
+        putBuild $ "| Install data " ++ f ++ " to " ++ dir
+    quietly $ cmd i fs dir
+
+-- | Install executable file to a directory
+installProgram :: FilePath -> FilePath -> Action ()
+installProgram f dir = do
+    i <- setting InstallProgram
+    putBuild $ "| Install program " ++ f ++ " to " ++ dir
+    quietly $ cmd i f dir
+
+-- | Install executable script to a directory
+installScript :: FilePath -> FilePath -> Action ()
+installScript f dir = do
+    i <- setting InstallScript
+    putBuild $ "| Install script " ++ f ++ " to " ++ dir
+    quietly $ cmd i f dir
+
+-- | Create a symbolic link from source file to target file when supported
+linkSymbolic :: FilePath -> FilePath -> Action ()
+linkSymbolic source target = do
+    lns <- setting LnS
+    when (lns /= "") $ do
+        need [source] -- Guarantee source is built before printing progress info.
+        let dir = takeDirectory target
+        liftIO $ IO.createDirectoryIfMissing True dir
+        putProgressInfo $ renderAction "Create symbolic link" source target
+        quietly $ cmd lns source target
+
 isInternal :: Builder -> Bool
 isInternal = isJust . builderProvenance
 



More information about the ghc-commits mailing list