From 10eaa9b6c0b76741a6dcd535e2a6e377df8d9109 Mon Sep 17 00:00:00 2001 From: Ross Paterson <ross@soi.city.ac.uk> Date: Mon, 4 Jun 2007 11:48:51 +0000 Subject: [PATCH] implement --configure-option and --ghc-option (#139) Added options used for building in the GHC tree: setup configure --configure-option=STR setup build --ghc-option=STR setup makefile --ghc-option=STR These were formerly scattered across Setup.hs files. --- Distribution/Make.hs | 3 +- Distribution/PackageDescription.hs | 11 ++++++ Distribution/Setup.hs | 43 +++++++++++++++++------ Distribution/Simple.hs | 2 +- Distribution/Simple/Build.hs | 11 ++++-- Setup.lhs | 54 +--------------------------- doc/Cabal.xml | 56 +++++++++++++++++++++++++++--- 7 files changed, 107 insertions(+), 73 deletions(-) diff --git a/Distribution/Make.hs b/Distribution/Make.hs index 98ce3e02f0..78e3f61f64 100644 --- a/Distribution/Make.hs +++ b/Distribution/Make.hs @@ -165,7 +165,8 @@ defaultMainHelper args _get_pkg_descr _ -> do putStrLn "Haddock Failed." exitWith retVal' - BuildCmd -> basicCommand "Build" "make" (parseBuildArgs args []) + BuildCmd -> basicCommand "Build" "make" + (parseBuildArgs emptyBuildFlags args []) MakefileCmd -> exitWith ExitSuccess -- presumably nothing to do diff --git a/Distribution/PackageDescription.hs b/Distribution/PackageDescription.hs index 229ca9e1c4..01804f4c91 100644 --- a/Distribution/PackageDescription.hs +++ b/Distribution/PackageDescription.hs @@ -70,6 +70,7 @@ module Distribution.PackageDescription ( -- * Build information BuildInfo(..), emptyBuildInfo, + mapBuildInfo, -- ** Supplementary build information HookedBuildInfo, @@ -405,6 +406,16 @@ emptyBuildInfo = BuildInfo { ghcProfOptions = [] } +-- | Modify all the 'BuildInfo's in a package description. +mapBuildInfo :: (BuildInfo -> BuildInfo) -> + PackageDescription -> PackageDescription +mapBuildInfo f pkg = pkg { + library = liftM mapLibBuildInfo (library pkg), + executables = map mapExeBuildInfo (executables pkg) } + where + mapLibBuildInfo lib = lib { libBuildInfo = f (libBuildInfo lib) } + mapExeBuildInfo exe = exe { buildInfo = f (buildInfo exe) } + type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)]) emptyHookedBuildInfo :: HookedBuildInfo diff --git a/Distribution/Setup.hs b/Distribution/Setup.hs index f5f7f3d079..c4e2b5f3c9 100644 --- a/Distribution/Setup.hs +++ b/Distribution/Setup.hs @@ -47,8 +47,10 @@ module Distribution.Setup (--parseArgs, ConfigFlags(..), emptyConfigFlags, configureArgs, CopyFlags(..), CopyDest(..), emptyCopyFlags, InstallFlags(..), emptyInstallFlags, - HaddockFlags(..), emptyHaddockFlags, emptyCleanFlags, - BuildFlags(..), CleanFlags(..), PFEFlags(..), + HaddockFlags(..), emptyHaddockFlags, + BuildFlags(..), emptyBuildFlags, + CleanFlags(..), emptyCleanFlags, + PFEFlags(..), MakefileFlags(..), emptyMakefileFlags, RegisterFlags(..), emptyRegisterFlags, SDistFlags(..), @@ -123,6 +125,7 @@ data ConfigFlags = ConfigFlags { configVanillaLib :: Bool, -- ^Enable vanilla library configProfLib :: Bool, -- ^Enable profiling in the library configProfExe :: Bool, -- ^Enable profiling in the executables. + configConfigureArgs :: [String], -- ^Extra arguments to @configure@ configOptimization :: Bool, -- ^Enable optimization. configPrefix :: Maybe FilePath, -- ^installation prefix @@ -162,6 +165,7 @@ emptyConfigFlags progConf = ConfigFlags { configVanillaLib = True, configProfLib = False, configProfExe = False, + configConfigureArgs = [], configOptimization = True, configCpphs = Nothing, configGreencard= Nothing, @@ -252,16 +256,20 @@ data CleanFlags = CleanFlags {cleanSaveConf :: Bool emptyCleanFlags :: CleanFlags emptyCleanFlags = CleanFlags {cleanSaveConf = False, cleanVerbose = normal} --- Following only have verbosity flags, but for consistency and --- extensibility we make them into a type. -data BuildFlags = BuildFlags {buildVerbose :: Verbosity} +data BuildFlags = BuildFlags {buildVerbose :: Verbosity + ,buildCompilerOptions :: [(CompilerFlavor, String)]} deriving Show +emptyBuildFlags :: BuildFlags +emptyBuildFlags = BuildFlags {buildVerbose = normal, buildCompilerOptions = []} + data MakefileFlags = MakefileFlags {makefileVerbose :: Verbosity, + makefileCompilerOptions :: [(CompilerFlavor, String)], makefileFile :: Maybe FilePath} deriving Show emptyMakefileFlags :: MakefileFlags emptyMakefileFlags = MakefileFlags {makefileVerbose = normal, + makefileCompilerOptions = [], makefileFile = Nothing} data PFEFlags = PFEFlags {pfeVerbose :: Verbosity} @@ -279,6 +287,7 @@ data Flag a = GhcFlag | NhcFlag | HugsFlag | JhcFlag | WithOptimization | WithoutOptimization | WithGHCiLib | WithoutGHCiLib | WithSplitObjs | WithoutSplitObjs + | ConfigureOption String | Prefix FilePath | BinDir FilePath @@ -291,6 +300,8 @@ data Flag a = GhcFlag | NhcFlag | HugsFlag | JhcFlag | ProgramArgs String String -- program name, arguments | WithProgram String FilePath -- program name, location + -- For build: + | GHCOption String -- For install, register, and unregister: | UserFlag | GlobalFlag -- for register & unregister @@ -344,7 +355,8 @@ configureArgs flags optFlag "bindir" configBinDir ++ optFlag "libdir" configLibDir ++ optFlag "libexecdir" configLibExecDir ++ - optFlag "datadir" configDataDir + optFlag "datadir" configDataDir ++ + configConfigureArgs flags where hc_flag = case (configHcFlavor flags, configHcPath flags) of (_, Just hc_path) -> ["--with-hc=" ++ hc_path] @@ -512,6 +524,7 @@ configureCmd progConf = Cmd { "split library into smaller objects to reduce binary sizes (GHC 6.6+)", Option "" ["disable-split-objs"] (NoArg WithoutSplitObjs) "split library into smaller objects to reduce binary sizes (GHC 6.6+)", + Option "" ["configure-option"] (ReqArg ConfigureOption "ARG") "Extra option for configure", Option "" ["user"] (NoArg UserFlag) "allow dependencies to be satisfied from the user package database. also implies install --user", Option "" ["global"] (NoArg GlobalFlag) @@ -591,27 +604,36 @@ parseConfigureArgs progConf = parseArgs (configureCmd progConf) updateCfg updateCfg t GlobalFlag = t { configUser = False } updateCfg t WithSplitObjs = t { configSplitObjs = True } updateCfg t WithoutSplitObjs = t { configSplitObjs = False } + updateCfg t (ConfigureOption s) = t { configConfigureArgs = configConfigureArgs t ++ [s] } updateCfg t (Lift _) = t updateCfg _ _ = error $ "Unexpected flag!" +cmd_ghc_option :: OptDescr (Flag a) +cmd_ghc_option = Option "" ["ghc-option"] (ReqArg GHCOption "ARG") "Extra option for GHC" + buildCmd :: Cmd a buildCmd = Cmd { cmdName = "build", cmdHelp = "Make this package ready for installation.", cmdDescription = "", -- This can be a multi-line description - cmdOptions = [cmd_help, cmd_verbose], + cmdOptions = [cmd_help, cmd_verbose, cmd_ghc_option], cmdAction = BuildCmd } -parseBuildArgs :: [String] -> [OptDescr a] -> IO (BuildFlags, [a], [String]) -parseBuildArgs = parseNoArgs buildCmd BuildFlags +parseBuildArgs :: BuildFlags -> [String] -> [OptDescr a] -> IO (BuildFlags, [a], [String]) +parseBuildArgs = parseArgs buildCmd updateArgs + where updateArgs bflags fl = + case fl of + Verbose n -> bflags{buildVerbose=n} + GHCOption s -> bflags{buildCompilerOptions=buildCompilerOptions bflags ++ [(GHC,s)] } + _ -> error "Unexpected flag!" makefileCmd :: Cmd a makefileCmd = Cmd { cmdName = "makefile", cmdHelp = "Perform any necessary makefileing.", cmdDescription = "", -- This can be a multi-line description - cmdOptions = [cmd_help, cmd_verbose, + cmdOptions = [cmd_help, cmd_verbose, cmd_ghc_option, Option "f" ["file"] (reqPathArg MakefileFile) "Filename to use (default: Makefile)."], cmdAction = MakefileCmd @@ -622,6 +644,7 @@ parseMakefileArgs = parseArgs makefileCmd updateCfg where updateCfg mflags fl = case fl of Verbose n -> mflags{makefileVerbose=n} + GHCOption s -> mflags{makefileCompilerOptions=makefileCompilerOptions mflags ++ [(GHC,s)] } MakefileFile f -> mflags{makefileFile=Just f} _ -> error "Unexpected flag!" diff --git a/Distribution/Simple.hs b/Distribution/Simple.hs index f6a42bd4d0..51c575a379 100644 --- a/Distribution/Simple.hs +++ b/Distribution/Simple.hs @@ -312,7 +312,7 @@ defaultMainWorker get_pkg_descr action all_args hooks prog_conf postConf hooks args flags' pkg_descr localbuildinfo BuildCmd -> - command parseBuildArgs buildVerbose + command (parseBuildArgs emptyBuildFlags) buildVerbose preBuild buildHook postBuild getPersistBuildConfig diff --git a/Distribution/Simple/Build.hs b/Distribution/Simple/Build.hs index e64269c8f3..76b3b66063 100644 --- a/Distribution/Simple/Build.hs +++ b/Distribution/Simple/Build.hs @@ -53,7 +53,7 @@ import Distribution.Compiler ( Compiler(..), CompilerFlavor(..) ) import Distribution.PackageDescription ( PackageDescription(..), BuildInfo(..), setupMessage, Executable(..), Library(..), - autogenModuleName ) + autogenModuleName, mapBuildInfo ) import Distribution.Package ( PackageIdentifier(..), showPackageId ) import Distribution.Setup ( CopyDest(..), BuildFlags(..), MakefileFlags(..) ) @@ -94,7 +94,10 @@ build :: PackageDescription -- ^mostly information from the .cabal file -> BuildFlags -- ^Flags that the user passed to build -> [ PPSuffixHandler ] -- ^preprocessors to run before compiling -> IO () -build pkg_descr lbi (BuildFlags verbosity) suffixes = do +build orig_pkg_descr lbi flags suffixes = do + let verbosity = buildVerbose flags + let addOptions bi = bi { options = options bi ++ [(comp, [opt]) | (comp, opt) <- buildCompilerOptions flags] } + let pkg_descr = mapBuildInfo addOptions orig_pkg_descr initialBuildSteps pkg_descr lbi verbosity suffixes setupMessage verbosity "Building" pkg_descr case compilerFlavor (compiler lbi) of @@ -109,8 +112,10 @@ makefile :: PackageDescription -- ^mostly information from the .cabal file -> MakefileFlags -- ^Flags that the user passed to makefile -> [ PPSuffixHandler ] -- ^preprocessors to run before compiling -> IO () -makefile pkg_descr lbi flags suffixes = do +makefile orig_pkg_descr lbi flags suffixes = do let verb = makefileVerbose flags + let addOptions bi = bi { options = options bi ++ [(comp, [opt]) | (comp, opt) <- makefileCompilerOptions flags] } + let pkg_descr = mapBuildInfo addOptions orig_pkg_descr initialBuildSteps pkg_descr lbi verb suffixes when (not (hasLibs pkg_descr)) $ die ("Makefile is only supported for libraries, currently.") diff --git a/Setup.lhs b/Setup.lhs index 6d92f1d8d1..4440e8cc47 100644 --- a/Setup.lhs +++ b/Setup.lhs @@ -2,59 +2,7 @@ > module Main (main) where > -> import Data.List > import Distribution.Simple -> import Distribution.PackageDescription -> import Distribution.Setup -> import Distribution.Simple.LocalBuildInfo -> import System.Environment > > main :: IO () -> main = do args <- getArgs -> let (ghcArgs, args') = extractGhcArgs args -> (_, args'') = extractConfigureArgs args' -> hooks = defaultUserHooks { -> buildHook = add_ghc_options ghcArgs -> $ buildHook defaultUserHooks } -> withArgs args'' $ defaultMainWithHooks hooks -> -> extractGhcArgs :: [String] -> ([String], [String]) -> extractGhcArgs = extractPrefixArgs "--ghc-option=" -> -> extractConfigureArgs :: [String] -> ([String], [String]) -> extractConfigureArgs = extractPrefixArgs "--configure-option=" -> -> extractPrefixArgs :: String -> [String] -> ([String], [String]) -> extractPrefixArgs the_prefix args -> = let f [] = ([], []) -> f (x:xs) = case f xs of -> (wantedArgs, otherArgs) -> -> case removePrefix the_prefix x of -> Just wantedArg -> -> (wantedArg:wantedArgs, otherArgs) -> Nothing -> -> (wantedArgs, x:otherArgs) -> in f args -> -> removePrefix :: String -> String -> Maybe String -> removePrefix "" ys = Just ys -> removePrefix _ "" = Nothing -> removePrefix (x:xs) (y:ys) -> | x == y = removePrefix xs ys -> | otherwise = Nothing -> -> type Hook a = PackageDescription -> LocalBuildInfo -> UserHooks -> a -> -> IO () -> -> add_ghc_options :: [String] -> Hook a -> Hook a -> add_ghc_options args f pd lbi uhs x -> = do let lib' = case library pd of -> Just lib -> -> let bi = libBuildInfo lib -> opts = options bi ++ [(GHC, args)] -> bi' = bi { options = opts } -> in lib { libBuildInfo = bi' } -> Nothing -> error "Expected a library" -> pd' = pd { library = Just lib' } -> f pd' lbi uhs x - +> main = defaultMain diff --git a/doc/Cabal.xml b/doc/Cabal.xml index 254d694a73..352d273bfa 100644 --- a/doc/Cabal.xml +++ b/doc/Cabal.xml @@ -1682,6 +1682,17 @@ runhaskell Setup.hs unregister --gen-script</screen> library or programs will be slower.</para> </listitem> </varlistentry> + + <varlistentry> + <term><option>--configure-option</option>=<replaceable>str</replaceable></term> + <listitem> + <para>An extra option to an external + <filename>configure</filename> script, + if one is used (see <xref linkend="system-dependent"/>). + There can be several of these options.</para> + </listitem> + </varlistentry> + </variablelist> <para>In the simple build infrastructure, an additional option @@ -1704,16 +1715,30 @@ runhaskell Setup.hs unregister --gen-script</screen> <title>setup build</title> <para>Perform any preprocessing or compilation needed to make this package ready for installation.</para> + + <para>This command takes the following option:</para> + + <variablelist> + <varlistentry> + <term><option>--ghc-option</option>=<replaceable>str</replaceable></term> + <listitem> + <para>An extra option to GHC, added after those specified in + the package description. There can be several of these + options.</para> + </listitem> + </varlistentry> + </variablelist> + </sect2> <sect2 id="setup-makefile"> <title>setup makefile</title> - <para>Generate a Makefile that may be used to compile the - Haskell modules to object code. This command is currently only - supported when building libraries, and only if the compiler is - GHC.</para> + <para>Generate a <filename>Makefile</filename> that may be used + to compile the Haskell modules to object code. + This command is currently only supported when building libraries, + and only if the compiler is GHC.</para> - <para>The makefile replaces part of the work done by + <para>The makefile command replaces part of the work done by <literal>setup build</literal>. The sequence of commands would typeically be: <programlisting> @@ -1746,6 +1771,27 @@ runhaskell Setup.hs build </itemizedlist> </para> + <para>This command takes the following options:</para> + + <variablelist> + <varlistentry> + <term><option>--file</option>=<replaceable>filename</replaceable> or + <option>-f</option> <replaceable>filename</replaceable></term> + <listitem> + <para>Specify the output file (default <filename>Makefile</filename>).</para> + </listitem> + </varlistentry> + + <varlistentry> + <term><option>--ghc-option</option>=<replaceable>str</replaceable></term> + <listitem> + <para>An extra option to GHC, added after those specified in + the package description. There can be several of these + options.</para> + </listitem> + </varlistentry> + </variablelist> + </sect2> <sect2 id="setup-haddock"> -- GitLab