#!/usr/bin/runghc \begin{code} import Distribution.PackageDescription import Distribution.Setup import Distribution.Simple import Distribution.Simple.LocalBuildInfo import Distribution.Simple.Utils(rawSystemVerbose) import System.Info import System.Exit import System.Directory import System.Process(runInteractiveProcess, waitForProcess) import System.IO(hClose, hGetContents, hPutStr, stderr) import Control.Monad(when) import Control.Exception(try) main = defaultMainWithHooks defaultUserHooks{preConf=preConf, postConf=postConf} where preConf :: [String] -> ConfigFlags -> IO HookedBuildInfo preConf args flags = do try (removeFile "SQLite3.buildinfo") return emptyHookedBuildInfo postConf :: [String] -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO ExitCode postConf args flags _ localbuildinfo = do mb_bi <- pkgConfigBuildInfo (configVerbose flags) "sqlite3" let bi = case mb_bi of Just bi -> bi Nothing -> emptyBuildInfo{extraLibs=["sqlite3"]} writeHookedBuildInfo "SQLite3.buildinfo" (Just bi,[]) return ExitSuccess \end{code} The following code is derived from Distribution.Simple.Configure \begin{code} findProgram :: String -- ^ program name -> Maybe FilePath -- ^ optional explicit path -> IO (Maybe FilePath) findProgram name Nothing = do mb_path <- findExecutable name case mb_path of Nothing -> message ("No " ++ name ++ " found") Just path -> message ("Using " ++ name ++ ": " ++ path) return mb_path findProgram name (Just path) = do message ("Using " ++ name ++ ": " ++ path) return (Just path) rawSystemGrabOutput :: Int -> FilePath -> [String] -> IO String rawSystemGrabOutput verbose path args = do when (verbose > 0) $ putStrLn (path ++ concatMap (' ':) args) (inp,out,err,pid) <- runInteractiveProcess path args Nothing Nothing exitCode <- waitForProcess pid if exitCode /= ExitSuccess then do errMsg <- hGetContents err hPutStr stderr errMsg exitWith exitCode else return () hClose inp hClose err hGetContents out message :: String -> IO () message s = putStrLn $ "configure: " ++ s \end{code} Populate BuildInfo using pkg-config tool. \begin{code} pkgConfigBuildInfo :: Int -> String -> IO (Maybe BuildInfo) pkgConfigBuildInfo verbose pkgName = do mb_pkg_config_path <- findProgram "pkg-config" Nothing case mb_pkg_config_path of Just pkg_config_path -> do message ("configuring "++pkgName++" package using pkg-config") res <- rawSystemGrabOutput verbose pkg_config_path [pkgName, "--libs-only-l"] let libs = map (tail.tail) (words res) res <- rawSystemGrabOutput verbose pkg_config_path [pkgName, "--libs-only-L"] let lib_dirs = map (tail.tail) (words res) res <- rawSystemGrabOutput verbose pkg_config_path [pkgName, "--libs-only-other"] let ld_opts = words res res <- rawSystemGrabOutput verbose pkg_config_path [pkgName, "--cflags-only-I"] let inc_dirs = map (tail.tail) (words res) res <- rawSystemGrabOutput verbose pkg_config_path [pkgName, "--cflags-only-other"] let cc_opts = words res let bi = emptyBuildInfo{extraLibs=libs, extraLibDirs=lib_dirs, ldOptions=ld_opts, includeDirs=inc_dirs, ccOptions=cc_opts} return (Just bi) Nothing -> do message ("The package will be built using default settings for "++pkgName) return Nothing \end{code}