#!/usr/bin/env runhaskell \begin{code} {-# OPTIONS -Wall -cpp #-} import Control.Monad import Data.List import Distribution.PackageDescription import Distribution.Simple import Distribution.Simple.LocalBuildInfo import Distribution.Simple.Utils import Distribution.Simple.Setup import System.Cmd import System.FilePath import System.Console.GetOpt import System.Exit import System.Directory import Control.Exception main :: IO () main = do let hooks = simpleUserHooks { preConf = generateConfigHs } defaultMainWithHooks hooks \end{code} \begin{code} data CoreLinkerFlag = TopDir FilePath | PkgConf FilePath deriving (Eq, Show) coreLinkerOptions :: [OptDescr CoreLinkerFlag] coreLinkerOptions = [Option [] ["topdir"] (ReqArg TopDir "DIRECTORY") ("Directory d that contains the library files for your stage 2 GHC build.\n" ++ "In an inplace build of GHC, this will be inplace_datadir inside your\n" ++ "top-level GHC build tree."), Option [] ["pkgconf"] (ReqArg PkgConf "FILEPATH") ("Location of the package.conf file pointing to your packages for the GHC\n" ++ "standard libraries that you've built ext-core for. If you built your\n" ++ "External Core libraries under $GHC, this file should live in $GHC/inplace-datadir/package.conf.")] getDirs :: [CoreLinkerFlag] -> Maybe (FilePath, FilePath) getDirs args = case findTopDir args of Just (TopDir f) -> case findPkgConf args of Just (PkgConf f1) -> Just (f,f1) _ -> Nothing _ -> Nothing findTopDir, findPkgConf :: [CoreLinkerFlag] -> Maybe CoreLinkerFlag findTopDir = find isTopDir findPkgConf = find isPkgConf isTopDir, isPkgConf :: CoreLinkerFlag -> Bool isTopDir (TopDir _) = True isTopDir _ = False isPkgConf (PkgConf _) = True isPkgConf _ = False generateConfigHs :: Args -> ConfigFlags -> IO HookedBuildInfo generateConfigHs _ confFlags = do let userConfigArgs = configConfigureArgs confFlags case getOpt Permute coreLinkerOptions userConfigArgs of (opts,_,_) -> case getDirs opts of Just (topDir,pkgConf) -> writeConfigHs topDir pkgConf Nothing -> error "To build the Core linker, you must supply a top-level directory containing your stage 2 GHC build, as well as the location of your packageconf file. For example: --configure-option=--topdir=your_ghc_build/inplace-datadir/ --configure-option=--pkgconf=your_stage1_ghc_build/inplace-datadir/package.conf" return emptyHookedBuildInfo writeConfigHs :: FilePath -> FilePath -> IO () writeConfigHs topDir pkgConf = writeFile "Config.hs" ("module Config where\nimport System.FilePath\nghcTopDir::FilePath\nghcTopDir =\"" ++ topDir ++ "\"\npkgConf::FilePath\npkgConf=\"" ++ pkgConf ++ "\"\n") type Hook a = PackageDescription -> LocalBuildInfo -> UserHooks -> a -> IO () -- Hack: If PrimEnv.hs exists *and* genprimopcode or -- primops.txt doesn't exist, don't rebuild PrimEnv.hs build_primitive_sources :: Hook a -> Hook a build_primitive_sources f pd lbi uhs x = do when (compilerFlavor (compiler lbi) == GHC) $ do let genprimopcode = joinPath ["..", "..", "utils", "genprimopcode", "genprimopcode"] primops = joinPath ["..", "..", "compiler", "prelude", "primops.txt"] primhs = joinPath ["Language", "Core", "PrimEnv.hs"] primhs_tmp = addExtension primhs "tmp" primEnvExists <- doesFileExist primhs genprimopcodeExists <- doesFileExist genprimopcode primopsExists <- doesFileExist primops unless (primEnvExists && not genprimopcodeExists && not primopsExists) $ do maybeExit $ system (genprimopcode ++ " --make-ext-core-source < " ++ primops ++ " > " ++ primhs_tmp) maybeUpdateFile primhs_tmp primhs maybeExit $ system ("make -C lib/GHC_ExtCore") f pd lbi uhs x -- Replace a file only if the new version is different from the old. -- This prevents make from doing unnecessary work after we run 'setup makefile' maybeUpdateFile :: FilePath -> FilePath -> IO () maybeUpdateFile source target = do r <- rawSystem "cmp" ["-s" {-quiet-}, source, target] case r of ExitSuccess -> removeFile source ExitFailure _ -> do #if __GLASGOW_HASKELL__ >= 610 (try :: IO () -> IO (Either IOException ())) #else try #endif (removeFile target) renameFile source target \end{code}