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

Commit 08d4377

Browse files
committed
Merge pull request #233 from haskell/minimal-full-split
Platform Changes for the Get Haskell Experience
2 parents b3212f4 + 6d9a145 commit 08d4377

24 files changed

+428
-184
lines changed

hptool/src/Config.hs

Lines changed: 18 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,8 @@ module Config
55
( askHpRelease
66
, askGhcBinDistTarFile
77
, askBuildConfig
8-
98
, addConfigOracle
9+
, askStackExe
1010
)
1111
where
1212

@@ -66,23 +66,35 @@ newtype BuildConfigQ = BuildConfigQ ()
6666
askBuildConfig :: Action BuildConfig
6767
askBuildConfig = readOracle "BuildConfig" (BuildConfigQ ())
6868

69+
newtype StackExeQ = StackExeQ ()
70+
deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
71+
72+
-- | Provide the stack executable
73+
-- The filepath will be tracked as a dependency
74+
askStackExe :: Action FilePath
75+
askStackExe = do
76+
stackexe <- askOracle $ StackExeQ ()
77+
need [stackexe]
78+
return stackexe
6979

70-
addConfigOracle :: Release -> FilePath -> Maybe FilePath -> Rules BuildConfig
71-
addConfigOracle hpRel tarFile prefix = do
80+
addConfigOracle :: Release -> FilePath -> FilePath -> Maybe FilePath -> Bool -> Rules BuildConfig
81+
addConfigOracle hpRel tarFile stackexe prefix includeExtra = do
7282
_ <- addOracle $
7383
\(HpReleaseQ _) -> return $ show hpRel
7484
_ <- addOracle $
7585
\(GhcBinDistTarFileQ _) -> return tarFile
86+
_ <- addOracle $
87+
\(StackExeQ _) -> return stackexe
7688
_ <- addOracle $
7789
\(BuildConfigQ _) -> either fail (return . show) buildConfig
7890
either fail return buildConfig
7991
where
80-
buildConfig = extractBuildConfig hpRel tarFile prefix
92+
buildConfig = extractBuildConfig hpRel tarFile prefix includeExtra
8193

8294

83-
extractBuildConfig :: Release -> FilePath -> Maybe FilePath
95+
extractBuildConfig :: Release -> FilePath -> Maybe FilePath -> Bool
8496
-> Either String BuildConfig
85-
extractBuildConfig hpRel tarFile prefix =
97+
extractBuildConfig hpRel tarFile prefix bcIncludeExtra =
8698
if ok then Right $ BuildConfig {..}
8799
else Left $ "extractBuildConfig tar file unparseable: " ++ base
88100
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: 17 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ import Development.Shake
88
import Development.Shake.FilePath
99
import System.Console.GetOpt
1010
import qualified System.Info (os, arch)
11+
import System.IO
1112

1213
import Config
1314
import Dirs
@@ -23,27 +24,29 @@ import Types
2324
import Target
2425
import Website
2526

26-
data Flags = Info | Prefix String
27+
data Flags = Info | Prefix String | Full
2728
deriving Eq
2829

2930
flags :: [OptDescr (Either a Flags)]
3031
flags = [ Option ['i'] ["info"] (NoArg $ Right Info)
3132
"Show info on what gets included in this HP release"
3233
, Option [] ["prefix"] (ReqArg (Right . Prefix) "DIR")
3334
"Set installation prefix (only for Posix builds)"
35+
, Option ['f'] ["full"] (NoArg $ Right Full)
36+
"Do a full (rather than minimal) build of the platform."
3437
]
3538

3639
main :: IO ()
37-
main = shakeArgsWith opts flags main'
40+
main = hSetEncoding stdout utf8 >> shakeArgsWith opts flags main'
3841
where
3942
main' flgs args =
4043
if Info `elem` flgs
4144
then info
4245
else case args of
43-
(tarfile:what) -> return $ Just $ do
44-
allRules tarfile flgs
45-
want $ if null what then ["build-all"] else what
46-
[] -> usage
46+
(tarfile:stackexe:buildType) -> return $ Just $ do
47+
allRules tarfile stackexe flgs
48+
want $ if null buildType then ["build-all"] else buildType
49+
_ -> usage
4750

4851
info = do
4952
putStrLn $ "This hptool is built to construct " ++ hpFullName ++ "\n\
@@ -55,7 +58,7 @@ main = shakeArgsWith opts flags main'
5558

5659
usage = do
5760
putStrLn "usage: hptool --info\n\
58-
\ hptool [opts] <ghc-bindist.tar.bz> [target...]\n\
61+
\ hptool [opts] <ghc-bindist.tar.bz> <stack executable> [target...]\n\
5962
\ where target is one of:\n\
6063
\ build-all -- build everything (default)\n\
6164
\ build-source -- build the source tar ball\n\
@@ -65,8 +68,8 @@ main = shakeArgsWith opts flags main'
6568
\ build-website -- build the website\n"
6669
return Nothing
6770

68-
allRules tarfile flgs = do
69-
buildConfig <- addConfigOracle hpRelease tarfile (prefixSetting flgs)
71+
allRules tarfile stackexe flgs = do
72+
buildConfig <- addConfigOracle hpRelease tarfile stackexe (prefixSetting flgs) (Full `elem` flgs)
7073
ghcDistRules
7174
packageRules
7275
targetRules buildConfig
@@ -82,13 +85,15 @@ main = shakeArgsWith opts flags main'
8285

8386
opts = shakeOptions
8487

85-
hpRelease = hp_7_10_3
88+
hpRelease = hp_8_0_0
8689
hpFullName = show $ relVersion hpRelease
8790
srcTarFile = productDir </> hpFullName <.> "tar.gz"
8891

8992

9093
whatIsIncluded :: Release -> [String]
91-
whatIsIncluded = map concat . map includeToString . relIncludes where
94+
whatIsIncluded rel = ("-- Minimal Platform:":minimalIncludes) ++ ("-- Full Platform:":fullIncludes) where
95+
minimalIncludes = map (concat . includeToString) $ relMinimalIncludes rel
96+
fullIncludes = map (concat . includeToString) $ relIncludes rel where
9297
includeToString (IncGHC, p) = "GHC: " : [show p]
9398
includeToString (IncGHCLib, p) = "GHCLib: " : [show p]
9499
includeToString (IncLib, p) = "LIB: " : [show p]
@@ -106,7 +111,7 @@ buildRules hpRelease srcTarFile bc = do
106111
"build-product" ~> need [osProduct]
107112
"build-local" ~> need [dir ghcLocalDir]
108113
"build-website" ~> need [dir websiteDir]
109-
forM_ (platformPackages hpRelease) $ \pkg -> do
114+
forM_ (platformPackages True hpRelease) $ \pkg -> do
110115
let full = "build-package-" ++ show pkg
111116
let short = "build-package-" ++ pkgName pkg
112117
short ~> need [full]
@@ -117,5 +122,3 @@ buildRules hpRelease srcTarFile bc = do
117122
osRules hpRelease bc
118123
where
119124
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/Mac.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ import Paths
1616
import Templates
1717
import Types
1818
import Utils
19+
import Config
1920

2021
macOsFromConfig :: BuildConfig -> OS
2122
macOsFromConfig BuildConfig{..} = OS{..}
@@ -79,7 +80,7 @@ macOsFromConfig BuildConfig{..} = OS{..}
7980
copyFile' f $ hpDocDir </> takeFileName f
8081

8182
productName =
82-
"Haskell Platform " ++ showVersion hpVersion ++ archBits bcArch
83+
"Haskell Platform " ++ showVersion hpVersion ++ (if bcIncludeExtra then " Full" else " Minimal") ++ archBits bcArch
8384

8485
osProduct = productDir </> productName <.> "pkg"
8586
signedProduct = productDir </> (productName ++ "-signed") <.> "pkg"
@@ -109,7 +110,8 @@ macOsFromConfig BuildConfig{..} = OS{..}
109110
makeDirectory hpBinDir
110111
need [dir extrasDir]
111112
binFiles <- getDirectoryFiles "" [extrasDir </> "bin/*"]
112-
forM_ binFiles $ \f -> do
113+
stackFile <- askStackExe
114+
forM_ (stackFile:binFiles) $ \f -> do
113115
if takeExtension f == ".hs"
114116
then compileToBin f $ hpBinDir </> takeBaseName f
115117
else copyFile' f $ hpBinDir </> takeFileName f
@@ -140,7 +142,7 @@ macOsFromConfig BuildConfig{..} = OS{..}
140142
command_ []
141143
"pkgbuild"
142144
[ "--identifier", "org.haskell.HaskellPlatform.Libraries."
143-
++ hpPkgMajorVer ++ ".pkg"
145+
++ hpPkgMajorVer ++ (if bcIncludeExtra then "-full" else "-minimal") ++ ".pkg"
144146
, "--version", hpPkgMinorVer
145147
, "--install-location", "/Library/Haskell"
146148
, "--root", "build/target/Library/Haskell"
@@ -153,7 +155,7 @@ macOsFromConfig BuildConfig{..} = OS{..}
153155
command_ []
154156
"productbuild"
155157
[ "--identifier", "org.haskell.HaskellPlatform."
156-
++ hpPkgMajorVer ++ ".pkg"
158+
++ hpPkgMajorVer ++ (if bcIncludeExtra then "-full" else "-minimal") ++ ".pkg"
157159
, "--version", hpPkgMinorVer
158160
, "--resources", osxInstallResources
159161
, "--distribution", osxInstallerDist

hptool/src/OS/Posix.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Development.Shake
1212
import Development.Shake.FilePath
1313

1414
import Dirs
15+
import Config
1516
import OS.Internal
1617
import Paths
1718
import Templates
@@ -71,7 +72,7 @@ posixOS BuildConfig{..} = OS{..}
7172
installScript = extrasDir </> "installer" </> "install-haskell-platform.sh"
7273

7374
productName =
74-
"haskell-platform-" ++ showVersion hpVersion ++ "-unknown-posix-" ++ bcArch
75+
"haskell-platform-" ++ showVersion hpVersion ++ "-unknown-posix-" ++ (if bcIncludeExtra then "-full-" else "-minimal-") ++ bcArch
7576

7677
genericExtrasSrc = "hptool/os-extras/posix"
7778

@@ -86,7 +87,7 @@ posixOS BuildConfig{..} = OS{..}
8687
need [ usrLocalTar, dir extrasDir]
8788
command_ [] "cp" [ installScript, productDir ]
8889
command_ [Cwd productDir]
89-
"tar" ["czf", out ® targetDir, installFile, usrLocalTar ® productDir ]
90+
"tar" ["czf", out `relativeToDir` targetDir, installFile, usrLocalTar `relativeToDir` productDir ]
9091
mapM_ putNormal
9192
[ replicate 72 '-'
9293
, "To install this build:"
@@ -98,7 +99,7 @@ posixOS BuildConfig{..} = OS{..}
9899
usrLocalTar %> \out -> do
99100
need [targetDir, vdir ghcVirtualTarget]
100101
command_ [Cwd targetDir]
101-
"tar" ["czf", out ® targetDir, hpTargetDir ® targetDir]
102+
"tar" ["czf", out `relativeToDir` targetDir, hpTargetDir `relativeToDir` targetDir]
102103

103104
versionFile %> \out -> do
104105
writeFileChanged out $ unlines
@@ -115,7 +116,8 @@ posixOS BuildConfig{..} = OS{..}
115116
makeDirectory hpBinDir
116117
need [dir extrasDir]
117118
binFiles <- getDirectoryFiles "" [extrasDir </> "bin/*"]
118-
forM_ binFiles $ \f -> do
119+
stackFile <- askStackExe
120+
forM_ (stackFile:binFiles) $ \f -> do
119121
copyFile' f $ hpBinDir </> takeFileName f
120122
return Nothing
121123

hptool/src/OS/Win.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -120,7 +120,7 @@ winOsFromConfig BuildConfig{..} = os
120120

121121
osDocAction = return ()
122122

123-
osProduct = winProductFile hpVersion bcArch
123+
osProduct = winProductFile bcIncludeExtra hpVersion bcArch
124124

125125
osRules _rel bc = do
126126
winRules

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 bcIncludeExtra 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/OS/Win/WinPaths.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -145,14 +145,14 @@ winDocTargetDir :: FilePath
145145
winDocTargetDir = winTargetDir </> "doc"
146146

147147
-- | The installer file name, dependent on the HP version and architecture
148-
winProductFileName :: Version -> String -> FilePath
149-
winProductFileName hpv arch =
148+
winProductFileName :: Bool -> Version -> String -> FilePath
149+
winProductFileName isFull hpv arch =
150150
("HaskellPlatform-" ++ versionAndArch ++ "-setup") <.> "exe"
151-
where versionAndArch = showVersion hpv ++ '-' : arch
151+
where versionAndArch = showVersion hpv ++ (if isFull then "-full" else "-minimal") ++ '-' : arch
152152

153153
-- | Directory where the installer file is built.
154-
winProductFile :: Version -> String -> FilePath
155-
winProductFile hpv arch = productDir </> winProductFileName hpv arch
154+
winProductFile :: Bool -> Version -> String -> FilePath
155+
winProductFile isFull hpv arch = productDir </> winProductFileName isFull hpv arch
156156

157157
-- | Relative to the install dir
158158
winGhcPackageDbDir :: FilePath
@@ -166,4 +166,3 @@ winGhcTargetPackageDbDir = winTargetDir </> winGhcPackageDbDir
166166
winNeeds :: [FilePath]
167167
winNeeds = [ nsisFile, nsisInstDat, nsisUninstDat ]
168168
++ winInstExtras
169-

0 commit comments

Comments
 (0)