#!/usr/bin/env runhaskell \begin{code} {-# OPTIONS -Wall -cpp #-} import Data.List import Distribution.PackageDescription import Distribution.Simple import Distribution.Simple.LocalBuildInfo import Distribution.Simple.Setup import System.Console.GetOpt main :: IO () main = do let hooks = simpleUserHooks { preConf = generateConfigHs } defaultMainWithHooks hooks \end{code} \begin{code} data CoreLinkerFlag = WithGhc FilePath | GhcFlag String deriving (Eq, Show) coreLinkerOptions :: [OptDescr CoreLinkerFlag] coreLinkerOptions = [Option [] ["with-ghc"] (ReqArg WithGhc "FILEPATH") ("Location of the GHC you want to use to compile files to Core.\n" ++ "Default is 'ghc'."), Option [] ["ghc-flag"] (ReqArg GhcFlag "STRING") ("A flag to pass to GHC. You may supply multiple --ghc-flag options.")] getGhc :: [CoreLinkerFlag] -> Maybe FilePath getGhc args = case findGhc args of Just (WithGhc g) -> Just g _ -> Nothing getFlags :: [CoreLinkerFlag] -> [String] getFlags = foldr (\ a rest -> case a of (GhcFlag s) -> s:rest _ -> rest) [] findGhc :: [CoreLinkerFlag] -> Maybe CoreLinkerFlag findGhc = find isGhc isGhc :: CoreLinkerFlag -> Bool isGhc (WithGhc _) = True isGhc _ = False generateConfigHs :: Args -> ConfigFlags -> IO HookedBuildInfo generateConfigHs _ confFlags = do let userConfigArgs = configConfigureArgs confFlags case getOpt Permute coreLinkerOptions userConfigArgs of (opts,_,_) -> case (getGhc opts,getFlags opts) of (Just ghc,fs) -> writeConfigHs ghc fs (Nothing,fs) -> putStrLn ("Warning: no ghc command supplied." ++ " Will default to 'ghc'.\nTo specify a different GHC " ++ "to use to build Core files, use the flag:\n" ++ "--configure-option=--with-ghc=/path/to/ghc") >> (writeConfigHs "ghc" fs) return emptyHookedBuildInfo writeConfigHs :: FilePath -> [String] -> IO () writeConfigHs ghcCmd flags = writeFile "Config.hs" ("module Config where\nghcStr::FilePath\nghcStr = \"" ++ ghcCmd ++ "\"\n" ++ showFlags ++ "\n") where showFlags = "ghcFlags::[String]\nghcFlags = " ++ show flags type Hook a = PackageDescription -> LocalBuildInfo -> UserHooks -> a -> IO () \end{code}