Skip to content
This repository was archived by the owner on Feb 3, 2022. It is now read-only.

Commit 6417e53

Browse files
U-CIQDEV\gbazermanU-CIQDEV\gbazerman
authored andcommitted
initial split release patch
1 parent 2ef782a commit 6417e53

17 files changed

+232
-66
lines changed

hptool/src/Config.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -67,8 +67,8 @@ askBuildConfig :: Action BuildConfig
6767
askBuildConfig = readOracle "BuildConfig" (BuildConfigQ ())
6868

6969

70-
addConfigOracle :: Release -> FilePath -> Maybe FilePath -> Rules BuildConfig
71-
addConfigOracle hpRel tarFile prefix = do
70+
addConfigOracle :: Release -> FilePath -> Maybe FilePath -> Bool -> Rules BuildConfig
71+
addConfigOracle hpRel tarFile prefix includeExtra = do
7272
_ <- addOracle $
7373
\(HpReleaseQ _) -> return $ show hpRel
7474
_ <- addOracle $
@@ -77,12 +77,12 @@ addConfigOracle hpRel tarFile prefix = do
7777
\(BuildConfigQ _) -> either fail (return . show) buildConfig
7878
either fail return buildConfig
7979
where
80-
buildConfig = extractBuildConfig hpRel tarFile prefix
80+
buildConfig = extractBuildConfig hpRel tarFile prefix includeExtra
8181

8282

83-
extractBuildConfig :: Release -> FilePath -> Maybe FilePath
83+
extractBuildConfig :: Release -> FilePath -> Maybe FilePath -> Bool
8484
-> Either String BuildConfig
85-
extractBuildConfig hpRel tarFile prefix =
85+
extractBuildConfig hpRel tarFile prefix bcIncludeExtra =
8686
if ok then Right $ BuildConfig {..}
8787
else Left $ "extractBuildConfig tar file unparseable: " ++ base
8888
where

hptool/src/GhcDist.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ ghcInstall postUntarAction base mfPrefix = do
4949
makeDirectory untarDir
5050

5151
command_ [Cwd untarDir]
52-
"tar" ["xf", tarFile ® untarDir]
52+
"tar" ["xf", tarFile `relativeToDir` untarDir]
5353

5454
case postUntarAction of
5555
GhcInstallConfigure -> ghcInstallConfigure base mfPrefix conf distDir
@@ -59,7 +59,7 @@ ghcInstall postUntarAction base mfPrefix = do
5959
ghcInstallConfigure :: FilePath -> Maybe (BuildConfig -> FilePath) -> GhcInstallAction
6060
ghcInstallConfigure base mfPrefix conf distDir = do
6161
let (prefix, destDir) = layout (($ conf) <$> mfPrefix)
62-
destArg = maybe [] (\_ -> ["DESTDIR=" ++ base ® distDir]) mfPrefix
62+
destArg = maybe [] (\_ -> ["DESTDIR=" ++ base `relativeToDir` distDir]) mfPrefix
6363
settingsFile = destDir </> "lib" </> show (bcGhcVersion conf) </> "settings"
6464

6565
configCmd <- liftIO $ absolutePath $ distDir </> "configure"

hptool/src/HaddockMaster.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -81,11 +81,11 @@ isForOS os i = okForAll
8181

8282
allCoreLibs :: Release -> BuildConfig -> [Package]
8383
allCoreLibs hpRel bc = packagesByIncludeFilter
84-
(\i -> isForOS (bcOs bc) i && isLib i && isGhc i) hpRel
84+
(\i -> isForOS (bcOs bc) i && isLib i && isGhc i) (bcIncludeExtra bc) hpRel
8585

8686
allPlatformLibs :: Release -> BuildConfig -> [Package]
8787
allPlatformLibs hpRel bc = packagesByIncludeFilter
88-
(\i -> isForOS (bcOs bc) i && isLib i && not (isGhc i)) hpRel
88+
(\i -> isForOS (bcOs bc) i && isLib i && not (isGhc i)) (bcIncludeExtra bc) hpRel
8989

9090

9191
haddockReadArg :: HaddockPkgLoc -> String
@@ -130,4 +130,3 @@ extractField field out = ex . lines $ out
130130
_ -> ex ls
131131

132132
fieldColon = field ++ ":"
133-

hptool/src/Main.hs

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -23,14 +23,16 @@ import Types
2323
import Target
2424
import Website
2525

26-
data Flags = Info | Prefix String
26+
data Flags = Info | Prefix String | Full
2727
deriving Eq
2828

2929
flags :: [OptDescr (Either a Flags)]
3030
flags = [ Option ['i'] ["info"] (NoArg $ Right Info)
3131
"Show info on what gets included in this HP release"
3232
, Option [] ["prefix"] (ReqArg (Right . Prefix) "DIR")
3333
"Set installation prefix (only for Posix builds)"
34+
, Option ['f'] ["full"] (NoArg $ Right Info)
35+
"Do a full (rather than minimal) build of the platform."
3436
]
3537

3638
main :: IO ()
@@ -66,7 +68,7 @@ main = shakeArgsWith opts flags main'
6668
return Nothing
6769

6870
allRules tarfile flgs = do
69-
buildConfig <- addConfigOracle hpRelease tarfile (prefixSetting flgs)
71+
buildConfig <- addConfigOracle hpRelease tarfile (prefixSetting flgs) (Full `elem` flgs)
7072
ghcDistRules
7173
packageRules
7274
targetRules buildConfig
@@ -82,13 +84,15 @@ main = shakeArgsWith opts flags main'
8284

8385
opts = shakeOptions
8486

85-
hpRelease = hp_7_10_3
87+
hpRelease = hp_8_0_0
8688
hpFullName = show $ relVersion hpRelease
8789
srcTarFile = productDir </> hpFullName <.> "tar.gz"
8890

8991

9092
whatIsIncluded :: Release -> [String]
91-
whatIsIncluded = map concat . map includeToString . relIncludes where
93+
whatIsIncluded rel = ("-- Minimal Platform:":minimalIncludes) ++ ("-- Full Platform:":fullIncludes) where
94+
minimalIncludes = map (concat . includeToString) $ relMinimalIncludes rel
95+
fullIncludes = map (concat . includeToString) $ relIncludes rel where
9296
includeToString (IncGHC, p) = "GHC: " : [show p]
9397
includeToString (IncGHCLib, p) = "GHCLib: " : [show p]
9498
includeToString (IncLib, p) = "LIB: " : [show p]
@@ -106,7 +110,7 @@ buildRules hpRelease srcTarFile bc = do
106110
"build-product" ~> need [osProduct]
107111
"build-local" ~> need [dir ghcLocalDir]
108112
"build-website" ~> need [dir websiteDir]
109-
forM_ (platformPackages hpRelease) $ \pkg -> do
113+
forM_ (platformPackages True hpRelease) $ \pkg -> do
110114
let full = "build-package-" ++ show pkg
111115
let short = "build-package-" ++ pkgName pkg
112116
short ~> need [full]
@@ -117,5 +121,3 @@ buildRules hpRelease srcTarFile bc = do
117121
osRules hpRelease bc
118122
where
119123
OS{..} = osFromConfig bc
120-
121-

hptool/src/OS/Internal.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ data OS = OS
3636
, osGhcTargetInstall :: GhcInstall
3737

3838
-- | Where each package is installed
39-
, osPackageTargetDir :: (PackagePattern p) => p -> FilePath
39+
, osPackageTargetDir :: forall p. (PackagePattern p) => p -> FilePath
4040

4141
-- | Set True if GHC in this build supports creating shared libs
4242
, osDoShared :: Bool
@@ -126,6 +126,6 @@ genericOS BuildConfig{..} = OS{..}
126126
osProduct %> \out -> do
127127
need [targetDir, vdir ghcVirtualTarget]
128128
command_ [Cwd buildRoot]
129-
"tar" ["czf", out ® buildRoot, targetDir ® buildRoot]
129+
"tar" ["czf", out `relativeToDir` buildRoot, targetDir `relativeToDir` buildRoot]
130130

131131
osPackageConfigureExtraArgs _pkg = []

hptool/src/OS/Posix.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,7 @@ posixOS BuildConfig{..} = OS{..}
8686
need [ usrLocalTar, dir extrasDir]
8787
command_ [] "cp" [ installScript, productDir ]
8888
command_ [Cwd productDir]
89-
"tar" ["czf", out ® targetDir, installFile, usrLocalTar ® productDir ]
89+
"tar" ["czf", out `relativeToDir` targetDir, installFile, usrLocalTar `relativeToDir` productDir ]
9090
mapM_ putNormal
9191
[ replicate 72 '-'
9292
, "To install this build:"
@@ -98,7 +98,7 @@ posixOS BuildConfig{..} = OS{..}
9898
usrLocalTar %> \out -> do
9999
need [targetDir, vdir ghcVirtualTarget]
100100
command_ [Cwd targetDir]
101-
"tar" ["czf", out ® targetDir, hpTargetDir ® targetDir]
101+
"tar" ["czf", out `relativeToDir` targetDir, hpTargetDir `relativeToDir` targetDir]
102102

103103
versionFile %> \out -> do
104104
writeFileChanged out $ unlines

hptool/src/OS/Win/WinNsis.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -44,8 +44,8 @@ genNsisData = do
4444
getDirContentsR winTargetDir
4545
where
4646
makeNativeRelPaths =
47-
map (\(d,fs) -> ( toNative $ d ® winTargetDir
48-
, map (toNative . (® winTargetDir)) fs))
47+
map (\(d,fs) -> ( toNative $ d `relativeToDir` winTargetDir
48+
, map (toNative . (`relativeToDir` winTargetDir)) fs))
4949

5050
genData tmpl file dirs = do
5151
ctx <- mu <$> pure tmpl <*> pure dirs
@@ -84,13 +84,13 @@ expandNsisInfo :: (Monad m) => Release -> BuildConfig -> MuContext m
8484
expandNsisInfo rls BuildConfig{..} = mkStrContext ex
8585
where
8686
ex "productFile" = MuVariable . toNative $
87-
winProductFile hpver bcArch ® installerPartsDir
87+
winProductFile hpver bcArch `relativeToDir` installerPartsDir
8888
-- NSIS tool needs to run from the installerPartsDir
8989
ex "build64bit" = MuBool is64
9090
ex "is32or64" = MuVariable $ if is64 then "64" else "32"
9191
ex "programFiles64" = MuVariable $ if is64 then "64" else ""
9292
ex "targetFiles" = MuVariable . toNative $
93-
winTargetDir ® takeDirectory nsisFile
93+
winTargetDir `relativeToDir` takeDirectory nsisFile
9494
-- NSIS is run from where nsisFile is, so make relative to that
9595

9696
ex _ = MuNothing

hptool/src/Package.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,8 @@ packageRules = do
5050

5151
listBuild %> \out -> do
5252
hpRel <- askHpRelease
53-
let pkgs = platformPackages hpRel
53+
bc <- askBuildConfig
54+
let pkgs = platformPackages (bcIncludeExtra bc) hpRel
5455
need $ map packageDepsFile pkgs
5556
nodes <- mapM buildNode pkgs
5657
writeFileLinesChanged out $ flattenSCCs $ stronglyConnComp nodes
@@ -87,7 +88,7 @@ installAction depFile hpRel = do
8788

8889
constraints =
8990
map (\p -> pkgName p ++ "==" ++ showVersion (pkgVersion p)) $
90-
allPackages hpRel
91+
(allPackages True) hpRel
9192

9293
decode out = case drop 1 $ lines out of
9394
("All the requested packages are already installed:":_) ->
@@ -100,5 +101,4 @@ installAction depFile hpRel = do
100101
++ unwords (filter (not . (`elem` packages)) deps)
101102
_ -> Left out
102103

103-
packages = map show $ allPackages hpRel
104-
104+
packages = map show $ (allPackages False) hpRel

hptool/src/PlatformDB.hs

Lines changed: 21 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,10 @@
11
module PlatformDB
2-
( release, deltaFrom,
2+
( release, releaseWithMinimal, deltaFrom,
33
incGHC, incGHCLib, incGHCTool, incLib, incTool,
44
notWindows, onlyWindows,
55

6+
allRelIncludes,
7+
68
allPackages,
79
corePackages,
810
platformPackages,
@@ -16,9 +18,17 @@ import Data.List (partition)
1618
import Types
1719
import Utils (version)
1820

19-
-- | Construct a release
21+
-- | both minimal and extra platform includes
22+
allRelIncludes :: Release -> [Include]
23+
allRelIncludes r = relMinimalIncludes r ++ relIncludes r
24+
25+
-- | Construct a release with a minimal partition
26+
releaseWithMinimal :: String -> [Include] -> [Include] -> Release
27+
releaseWithMinimal vstr minimalIncs incs = Release (HpVersion $ version vstr) minimalIncs incs
28+
29+
-- | Construct a release, when there is not a seperate minimal selection of includes with the main ones.
2030
release :: String -> [Include] -> Release
21-
release vstr incs = Release (HpVersion $ version vstr) incs
31+
release vstr incs = Release (HpVersion $ version vstr) incs []
2232

2333
-- | Construct list of Includes as a delta to packages in another release
2434
deltaFrom :: Release -> [Include] -> [Include]
@@ -69,20 +79,20 @@ notWindows (it, pkg) = (IncIfNotWindows it, pkg)
6979
onlyWindows :: Include -> Include
7080
onlyWindows (it, pkg) = (IncIfWindows it, pkg)
7181

82+
-- | Bool indicates if including extra packages
83+
packagesByIncludeFilter :: (IncludeType -> Bool) -> Bool -> Release -> [Package]
84+
packagesByIncludeFilter f extraPkgs = map snd . filter (f . fst) . if extraPkgs then allRelIncludes else relMinimalIncludes
7285

73-
packagesByIncludeFilter :: (IncludeType -> Bool) -> Release -> [Package]
74-
packagesByIncludeFilter f = map snd . filter (f . fst) . relIncludes
75-
76-
-- | All packages in the release
77-
allPackages :: Release -> [Package]
78-
allPackages = packagesByIncludeFilter $ const True
86+
-- | All packages in the release, bool indicates if including extra packages
87+
allPackages :: Bool -> Release -> [Package]
88+
allPackages = packagesByIncludeFilter (const True)
7989

8090
-- | Includes that are part of the core (expected to come with GHC)
81-
corePackages :: Release -> [Package]
91+
corePackages :: Bool -> Release -> [Package]
8292
corePackages = packagesByIncludeFilter isGhc
8393

8494
-- | Includes that come from the platform (added beyond the GHC default)
85-
platformPackages :: Release -> [Package]
95+
platformPackages :: Bool -> Release -> [Package]
8696
platformPackages = packagesByIncludeFilter (not . isGhc)
8797

8898
-- | Tests of Include

hptool/src/Releases.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module Releases
33
, module Releases2013
44
, module Releases2014
55
, module Releases2015
6+
, module Releases2016
67
, releases
78
)
89

@@ -12,6 +13,7 @@ import Releases2012
1213
import Releases2013
1314
import Releases2014
1415
import Releases2015
16+
import Releases2016
1517
import Types
1618

1719
releases :: [Release]
@@ -20,4 +22,5 @@ releases = concat
2022
, releases2013
2123
, releases2014
2224
, releases2015
25+
, releases2016
2326
]

0 commit comments

Comments
 (0)