@@ -60,7 +60,7 @@ main = do
60
60
msg $ " Bootstrapping GHC version: " ++ init ghc0_version
61
61
62
62
msg " Building stage1 GHC program and utility programs"
63
- buildGhcStage1 defaultGhcBuildOptions cabal ghc0
63
+ buildGhcStage1 defaultGhcBuildOptions cabal ghc0 " _build/stage0/ "
64
64
65
65
ghc1 <- Ghc <$> makeAbsolute " _build/stage0/bin/ghc"
66
66
ghcPkg1 <- GhcPkg <$> makeAbsolute " _build/stage0/bin/ghc-pkg"
@@ -69,17 +69,17 @@ main = do
69
69
genprimop <- GenPrimop <$> makeAbsolute " _build/stage0/bin/genprimopcode"
70
70
71
71
msg " Building boot libraries with stage1 compiler..."
72
- buildBootLibraries cabal ghc1 ghcPkg1 deriveConstants genapply genprimop defaultGhcBuildOptions
72
+ buildBootLibraries cabal ghc1 ghcPkg1 deriveConstants genapply genprimop defaultGhcBuildOptions " _build/stage1/ "
73
73
74
74
msg " Done"
75
75
76
76
77
77
-- | Build stage1 GHC program
78
- buildGhcStage1 :: GhcBuildOptions -> Cabal -> Ghc -> IO ()
79
- buildGhcStage1 opts cabal ghc0 = do
80
- prepareGhcSources opts " _build/stage0/ src/"
78
+ buildGhcStage1 :: GhcBuildOptions -> Cabal -> Ghc -> FilePath -> IO ()
79
+ buildGhcStage1 opts cabal ghc0 dst = do
80
+ prepareGhcSources opts (dst </> " src/" )
81
81
82
- let builddir = " _build/stage0/ cabal/ "
82
+ let builddir = dst </> " cabal"
83
83
createDirectoryIfMissing True builddir
84
84
85
85
-- we need to augment the current environment to pass HADRIAN_SETTINGS
@@ -120,13 +120,13 @@ buildGhcStage1 opts cabal ghc0 = do
120
120
{ env = Just stage1_env
121
121
}
122
122
(exit_code, cabal_stdout, cabal_stderr) <- readCreateProcessWithExitCode build_cmd " "
123
- writeFile " _build/stage0/ cabal.stdout" cabal_stdout
124
- writeFile " _build/stage0/ cabal.stderr" cabal_stderr
123
+ writeFile (dst </> " cabal.stdout" ) cabal_stdout
124
+ writeFile (dst </> " cabal.stderr" ) cabal_stderr
125
125
case exit_code of
126
126
ExitSuccess -> pure ()
127
127
ExitFailure n -> do
128
128
putStrLn $ " cabal-install failed with error code: " ++ show n
129
- putStrLn " Logs can be found in \" _build/stage0 /cabal.{stdout,stderr}\" "
129
+ putStrLn $ " Logs can be found in \" " ++ dst ++ " /cabal.{stdout,stderr}\" "
130
130
exitFailure
131
131
132
132
msg " - Copying stage1 programs and generating settings to use them..."
@@ -142,24 +142,24 @@ buildGhcStage1 opts cabal ghc0 = do
142
142
case list_bin_exit_code of
143
143
ExitSuccess
144
144
| (bin_src: _) <- lines list_bin_stdout
145
- -> cp bin_src (" _build/stage0/ bin" </> bin)
145
+ -> cp bin_src (dst </> " bin" </> bin)
146
146
_ -> do
147
147
putStrLn $ " Failed to run cabal list-bin for the target: " ++ show target
148
148
putStrLn list_bin_stderr
149
149
exitFailure
150
- createDirectoryIfMissing True " _build/stage0/ bin"
150
+ createDirectoryIfMissing True (dst </> " bin" )
151
151
copy_bin " ghc-bin:ghc" " ghc"
152
152
copy_bin " ghc-pkg:ghc-pkg" " ghc-pkg"
153
153
copy_bin " deriveConstants:deriveConstants" " deriveConstants"
154
154
copy_bin " genprimopcode:genprimopcode" " genprimopcode"
155
155
copy_bin " genapply:genapply" " genapply"
156
156
157
157
-- initialize empty global package database
158
- pkgdb <- makeAbsolute " _build/stage1/ pkgs"
158
+ pkgdb <- makeAbsolute (dst </> " pkgs" )
159
159
doesDirectoryExist pkgdb >>= \ case
160
160
True -> pure () -- don't try to recreate the DB if it already exist as it would fail
161
161
False -> do
162
- ghcpkg <- GhcPkg <$> makeAbsolute " _build/stage0/ bin/ghc-pkg"
162
+ ghcpkg <- GhcPkg <$> makeAbsolute (dst </> " bin/ghc-pkg" )
163
163
void $ readCreateProcess (runGhcPkg ghcpkg [" init" , pkgdb]) " "
164
164
void $ readCreateProcess (runGhcPkg ghcpkg
165
165
[ " recache"
@@ -169,13 +169,13 @@ buildGhcStage1 opts cabal ghc0 = do
169
169
170
170
171
171
-- generate settings based on stage1 compiler settings
172
- createDirectoryIfMissing True " _build/stage0/ lib"
172
+ createDirectoryIfMissing True (dst </> " lib" )
173
173
let stage1_settings = makeStage1Settings stage0_settings
174
- writeFile " _build/stage0/ lib/settings" (show stage1_settings)
174
+ writeFile (dst </> " lib/settings" ) (show stage1_settings)
175
175
176
176
-- try to run the stage1 compiler (no package db yet, so just display the
177
177
-- version)
178
- (test_exit_code, test_stdout, _test_stderr) <- readCreateProcessWithExitCode (proc " _build/stage0/ bin/ghc" [" --version" ]) " "
178
+ (test_exit_code, test_stdout, _test_stderr) <- readCreateProcessWithExitCode (proc (dst </> " bin/ghc" ) [" --version" ]) " "
179
179
case test_exit_code of
180
180
ExitSuccess -> pure ()
181
181
ExitFailure n -> do
@@ -339,22 +339,19 @@ makeStage1Settings in_settings = out_settings
339
339
340
340
, keep_def " target RTS linker only supports shared libraries" " NO"
341
341
, (" Use interpreter" , " NO" )
342
- , (" base unit-id" , " base" ) -- FIXME
342
+ , (" base unit-id" , " base" ) -- there is no base yet... Anyway this isn't really useful to set
343
343
, keep_fail " Support SMP"
344
344
, keep_fail " RTS ways"
345
345
, keep_fail " Tables next to code"
346
346
, keep_fail " Leading underscore"
347
347
, keep_fail " Use LibFFI"
348
348
, keep_fail " RTS expects libdw"
349
- , (" Relative Global Package DB" , " ../../stage1/ pkgs" )
349
+ , (" Relative Global Package DB" , " ../pkgs" )
350
350
]
351
351
352
- buildBootLibraries :: Cabal -> Ghc -> GhcPkg -> DeriveConstants -> GenApply -> GenPrimop -> GhcBuildOptions -> IO ()
353
- buildBootLibraries cabal ghc ghcpkg derive_constants genapply genprimop opts = do
354
- -- FIXME: should be parameters
355
- let dst = " _build/stage1/"
356
- src <- makeAbsolute " _build/stage1/src"
357
-
352
+ buildBootLibraries :: Cabal -> Ghc -> GhcPkg -> DeriveConstants -> GenApply -> GenPrimop -> GhcBuildOptions -> FilePath -> IO ()
353
+ buildBootLibraries cabal ghc ghcpkg derive_constants genapply genprimop opts dst = do
354
+ src <- makeAbsolute (dst </> " src" )
358
355
prepareGhcSources opts src
359
356
360
357
-- Build the RTS
0 commit comments