[Git][ghc/ghc][master] hadrian: introduce 'install' target

Marge Bot gitlab at gitlab.haskell.org
Fri May 29 05:42:46 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
f9a513e0 by Alp Mestanogullari at 2020-05-29T01:42:36-04:00
hadrian: introduce 'install' target

Its logic is very simple. It `need`s the `binary-dist-dir` target
and runs suitable `configure` and `make install` commands for the
user. A new `--prefix` command line argument is introduced to
specify where GHC should be installed.

- - - - -


3 changed files:

- hadrian/README.md
- hadrian/src/CommandLine.hs
- hadrian/src/Rules/BinaryDist.hs


Changes:

=====================================
hadrian/README.md
=====================================
@@ -258,6 +258,19 @@ $ ./configure [--prefix=PATH] && make install
 
 workflow, for now.
 
+### Building and installing GHC
+
+You can get Hadrian to build _and_ install a binary distribution in one go
+with the following command:
+
+``` sh
+$ build install --prefix=/some/absolute/path
+```
+
+This builds everything that would be shipped in a bindist, without creating
+the archive, and just runs `./configure --prefix=PATH` and `make install`
+to get GHC installed installed at `/some/absolute/path`.
+
 #### Building Stage3
 
 It is possible to define a build flavour that builds a Stage3 compiler, which is


=====================================
hadrian/src/CommandLine.hs
=====================================
@@ -1,7 +1,8 @@
 module CommandLine (
     optDescrs, cmdLineArgsMap, cmdFlavour, lookupFreeze1, lookupFreeze2,
     cmdIntegerSimple, cmdProgressInfo, cmdConfigure, cmdCompleteSetting,
-    cmdDocsArgs, lookupBuildRoot, TestArgs(..), TestSpeed(..), defaultTestArgs
+    cmdDocsArgs, lookupBuildRoot, TestArgs(..), TestSpeed(..), defaultTestArgs,
+    cmdPrefix
     ) where
 
 import Data.Either
@@ -30,6 +31,7 @@ data CommandLineArgs = CommandLineArgs
     , buildRoot      :: BuildRoot
     , testArgs       :: TestArgs
     , docTargets     :: DocTargets
+    , prefix         :: Maybe FilePath
     , completeStg    :: Maybe String }
     deriving (Eq, Show)
 
@@ -45,6 +47,7 @@ defaultCommandLineArgs = CommandLineArgs
     , buildRoot      = BuildRoot "_build"
     , testArgs       = defaultTestArgs
     , docTargets     = Set.fromList [minBound..maxBound]
+    , prefix         = Nothing
     , completeStg    = Nothing }
 
 -- | These arguments are used by the `test` target.
@@ -207,6 +210,9 @@ readBrokenTests way =
             let newTests = words tests ++ brokenTests (testArgs flags)
             in flags { testArgs = (testArgs flags) {brokenTests = newTests} }
 
+readPrefix :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
+readPrefix ms = Right $ \flags -> flags { prefix = ms }
+
 readCompleteStg :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
 readCompleteStg ms = Right $ \flags -> flags { completeStg = ms }
 
@@ -281,6 +287,8 @@ optDescrs =
     , Option [] ["broken-test"] (OptArg readBrokenTests "TEST_NAME")
       "consider these tests to be broken"
     , Option ['a'] ["test-accept"] (NoArg readTestAccept) "Accept new output of tests"
+    , Option [] ["prefix"] (OptArg readPrefix "PATH")
+        "Destination path for the bindist 'install' rule"
     , Option [] ["complete-setting"] (OptArg readCompleteStg "SETTING")
         "Setting key to autocomplete, for the 'autocomplete' target."
     ]
@@ -332,6 +340,9 @@ cmdConfigure = configure <$> cmdLineArgs
 cmdFlavour :: Action (Maybe String)
 cmdFlavour = flavour <$> cmdLineArgs
 
+cmdPrefix :: Action (Maybe String)
+cmdPrefix = prefix <$> cmdLineArgs
+
 cmdCompleteSetting :: Action (Maybe String)
 cmdCompleteSetting = completeStg <$> cmdLineArgs
 


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -2,6 +2,7 @@ module Rules.BinaryDist where
 
 import Hadrian.Haskell.Cabal
 
+import CommandLine
 import Context
 import Expression
 import Oracles.Setting
@@ -98,6 +99,18 @@ other, the install script:
 bindistRules :: Rules ()
 bindistRules = do
     root <- buildRootRules
+    phony "install" $ do
+        need ["binary-dist-dir"]
+        version        <- setting ProjectVersion
+        targetPlatform <- setting TargetPlatformFull
+        let ghcVersionPretty = "ghc-" ++ version ++ "-" ++ targetPlatform
+            bindistFilesDir  = root -/- "bindist" -/- ghcVersionPretty
+            prefixErr = "You must specify a path with --prefix when using the"
+                     ++ " 'install' rule"
+        installPrefix <- fromMaybe (error prefixErr) <$> cmdPrefix
+        runBuilder (Configure bindistFilesDir) ["--prefix="++installPrefix] [] []
+        runBuilder (Make bindistFilesDir) ["install"] [] []
+
     phony "binary-dist-dir" $ do
         -- We 'need' all binaries and libraries
         targets <- mapM pkgTarget =<< stagePackages Stage1



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f9a513e064bd8a33ad6f8aa5fb8673931507eca1

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f9a513e064bd8a33ad6f8aa5fb8673931507eca1
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200529/74fd3d42/attachment-0001.html>


More information about the ghc-commits mailing list