module Distribution.Simple.GHC (
configure, getInstalledPackages, build, makefile, installLib, installExe,
ghcVerbosityOptions
) where
import Distribution.Simple.GHC.Makefile
import Distribution.Simple.Setup ( MakefileFlags(..) )
import Distribution.PackageDescription
( PackageDescription(..), BuildInfo(..),
withLib, setupMessage,
Executable(..), withExe, Library(..),
libModules, hcOptions )
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..), autogenModulesDir )
import Distribution.Simple.Utils
import Distribution.Package ( PackageIdentifier(..), showPackageId,
parsePackageId )
import Distribution.Simple.Program ( rawSystemProgram, rawSystemProgramConf,
rawSystemProgramStdoutConf,
rawSystemProgramStdout,
Program(..), ConfiguredProgram(..),
ProgramConfiguration,
userMaybeSpecifyPath, requireProgram,
programPath, lookupProgram, updateProgram,
ghcProgram, ghcPkgProgram,
arProgram, ranlibProgram, ldProgram )
import Distribution.Simple.Compiler
import Distribution.Version ( Version(..), showVersion,
VersionRange(..), orLaterVersion )
import qualified Distribution.Simple.GHC.PackageConfig as GHC
( localPackageConfig,
canReadLocalPackageConfig )
import Distribution.System
import Distribution.Verbosity
import Language.Haskell.Extension (Extension(..))
import Distribution.Compat.ReadP
( readP_to_S, many, skipSpaces )
import Control.Monad ( unless, when )
import Data.Char
import Data.List ( nub, isPrefixOf )
import System.Directory ( removeFile, renameFile,
getDirectoryContents, doesFileExist )
import Distribution.Compat.Directory ( getTemporaryDirectory )
import Distribution.Compat.TempFile ( withTempFile )
import System.FilePath ( (</>), (<.>), takeExtension,
takeDirectory, replaceExtension, splitExtension )
import System.IO
import Control.Exception as Exception (handle)
#ifndef __NHC__
import Control.Exception as Try
#else
import IO as Try
#endif
configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration)
configure verbosity hcPath hcPkgPath conf = do
(ghcProg, conf') <- requireProgram verbosity ghcProgram
(orLaterVersion (Version [6,2] []))
(userMaybeSpecifyPath "ghc" hcPath conf)
let Just ghcVersion = programVersion ghcProg
(ghcPkgProg, conf'') <- requireProgram verbosity ghcPkgProgram {
programFindLocation = guessGhcPkgFromGhcPath ghcProg
}
(orLaterVersion (Version [0] []))
(userMaybeSpecifyPath "ghc-pkg" hcPkgPath conf')
let Just ghcPkgVersion = programVersion ghcPkgProg
when (ghcVersion /= ghcPkgVersion) $ die $
"Version mismatch between ghc and ghc-pkg:\n"
++ programPath ghcProg ++ " is version " ++ showVersion ghcVersion ++ "\n"
++ programPath ghcPkgProg ++ " is version " ++ showVersion ghcPkgVersion
let ldProgram' = case os of
Windows _ ->
let compilerDir = takeDirectory (programPath ghcProg)
baseDir = takeDirectory compilerDir
binInstallLd = baseDir </> "gcc-lib" </> "ld.exe"
in ldProgram {
programFindLocation = \_ -> return (Just binInstallLd)
}
_ -> ldProgram
(ldProg, conf''') <- requireProgram verbosity ldProgram' AnyVersion conf''
tempDir <- getTemporaryDirectory
ldx <- withTempFile tempDir "c" $ \testcfile ->
withTempFile tempDir "o" $ \testofile -> do
writeFile testcfile "int foo() {}\n"
rawSystemProgram verbosity ghcProg ["-c", testcfile,
"-o", testofile]
withTempFile tempDir "o" $ \testofile' ->
Exception.handle (\_ -> return False) $ do
rawSystemProgramStdout verbosity ldProg
["-x", "-r", testofile, "-o", testofile']
return True
let conf'''' = updateProgram ldProg {
programArgs = if ldx then ["-x"] else []
} conf'''
let isSep c = isSpace c || (c == ',')
languageExtensions <-
if ghcVersion >= Version [6,7] []
then do exts <- rawSystemStdout verbosity (programPath ghcProg)
["--supported-languages"]
return [ (ext, "-X" ++ show ext)
| extStr <- breaks isSep exts
, (ext, "") <- reads extStr ++ reads ("No" ++ extStr) ]
else return oldLanguageExtensions
let comp = Compiler {
compilerFlavor = GHC,
compilerId = PackageIdentifier "ghc" ghcVersion,
compilerExtensions = languageExtensions
}
return (comp, conf'''')
guessGhcPkgFromGhcPath :: ConfiguredProgram -> Verbosity -> IO (Maybe FilePath)
guessGhcPkgFromGhcPath ghcProg verbosity
= do let path = programPath ghcProg
dir = takeDirectory path
versionSuffix = takeVersionSuffix (dropExeExtension path)
guessNormal = dir </> "ghc-pkg" <.> exeExtension
guessVersioned = dir </> ("ghc-pkg" ++ versionSuffix) <.> exeExtension
guesses | null versionSuffix = [guessNormal]
| otherwise = [guessVersioned, guessNormal]
info verbosity $ "looking for package tool: ghc-pkg near compiler in " ++ dir
exists <- mapM doesFileExist guesses
case [ file | (file, True) <- zip guesses exists ] of
[] -> return Nothing
(pkgtool:_) -> do info verbosity $ "found package tool in " ++ pkgtool
return (Just pkgtool)
where takeVersionSuffix :: FilePath -> String
takeVersionSuffix = reverse . takeWhile (`elem ` "0123456789.-") . reverse
dropExeExtension :: FilePath -> FilePath
dropExeExtension filepath =
case splitExtension filepath of
(filepath', extension) | extension == exeExtension -> filepath'
| otherwise -> filepath
oldLanguageExtensions :: [(Extension, Flag)]
oldLanguageExtensions =
[(OverlappingInstances , "-fallow-overlapping-instances")
,(TypeSynonymInstances , "-fglasgow-exts")
,(TemplateHaskell , "-fth")
,(ForeignFunctionInterface , "-fffi")
,(NoMonomorphismRestriction , "-fno-monomorphism-restriction")
,(NoMonoPatBinds , "-fno-mono-pat-binds")
,(UndecidableInstances , "-fallow-undecidable-instances")
,(IncoherentInstances , "-fallow-incoherent-instances")
,(Arrows , "-farrows")
,(Generics , "-fgenerics")
,(NoImplicitPrelude , "-fno-implicit-prelude")
,(ImplicitParams , "-fimplicit-params")
,(CPP , "-cpp")
,(BangPatterns , "-fbang-patterns")
,(KindSignatures , fglasgowExts)
,(RecursiveDo , fglasgowExts)
,(ParallelListComp , fglasgowExts)
,(MultiParamTypeClasses , fglasgowExts)
,(FunctionalDependencies , fglasgowExts)
,(Rank2Types , fglasgowExts)
,(RankNTypes , fglasgowExts)
,(PolymorphicComponents , fglasgowExts)
,(ExistentialQuantification , fglasgowExts)
,(ScopedTypeVariables , "-fscoped-type-variables")
,(FlexibleContexts , fglasgowExts)
,(FlexibleInstances , fglasgowExts)
,(EmptyDataDecls , fglasgowExts)
,(PatternGuards , fglasgowExts)
,(GeneralizedNewtypeDeriving , fglasgowExts)
,(MagicHash , fglasgowExts)
,(UnicodeSyntax , fglasgowExts)
,(PatternSignatures , fglasgowExts)
,(UnliftedFFITypes , fglasgowExts)
,(LiberalTypeSynonyms , fglasgowExts)
,(TypeOperators , fglasgowExts)
,(GADTs , fglasgowExts)
,(RelaxedPolyRec , fglasgowExts)
,(ExtendedDefaultRules , "-fextended-default-rules")
,(UnboxedTuples , fglasgowExts)
,(DeriveDataTypeable , fglasgowExts)
,(ConstrainedClassMethods , fglasgowExts)
]
where
fglasgowExts = "-fglasgow-exts"
getInstalledPackages :: Verbosity -> PackageDB -> ProgramConfiguration
-> IO [PackageIdentifier]
getInstalledPackages verbosity packagedb conf = do
str <- rawSystemProgramStdoutConf verbosity ghcPkgProgram conf
[packageDbGhcPkgFlag packagedb, "list"]
let str1 = case packagedb of
UserPackageDB -> allFiles str
_ -> firstFile str
str2 = filter (`notElem` ",(){}") str1
case pCheck (readP_to_S (many (skipSpaces >> parsePackageId)) str2) of
[ps] -> return ps
_ -> die "cannot parse package list"
where
packageDbGhcPkgFlag GlobalPackageDB = "--global"
packageDbGhcPkgFlag UserPackageDB = "--user"
packageDbGhcPkgFlag (SpecificPackageDB path) = "--package-conf=" ++ path
pCheck :: [(a, [Char])] -> [a]
pCheck rs = [ r | (r,s) <- rs, all isSpace s ]
allFiles str = unlines $ filter keep_line $ lines str
where keep_line s = ':' `notElem` s && not ("Creating" `isPrefixOf` s)
firstFile str = unlines $ takeWhile (not . file_line) $
drop 1 $ dropWhile (not . file_line) $ lines str
where file_line s = ':' `elem` s && not ("Creating" `isPrefixOf` s)
build :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO ()
build pkg_descr lbi verbosity = do
let pref = buildDir lbi
runGhcProg = rawSystemProgramConf verbosity ghcProgram (withPrograms lbi)
ifVanillaLib forceVanilla = when (forceVanilla || withVanillaLib lbi)
ifProfLib = when (withProfLib lbi)
ifSharedLib = when (withSharedLib lbi)
ifGHCiLib = when (withGHCiLib lbi)
pkg_conf <- if versionBranch (compilerVersion (compiler lbi)) >= [6,4]
then return []
else do pkgConf <- GHC.localPackageConfig
pkgConfReadable <- GHC.canReadLocalPackageConfig
if pkgConfReadable
then return ["-package-conf", pkgConf]
else return []
withLib pkg_descr () $ \lib -> do
info verbosity "Building library..."
let libBi = libBuildInfo lib
libTargetDir = pref
forceVanillaLib = TemplateHaskell `elem` extensions libBi
createDirectoryIfMissingVerbose verbosity True libTargetDir
smartCopySources verbosity (hsSourceDirs libBi)
libTargetDir (libModules pkg_descr) ["hi-boot"] False False
let ghc_vers = compilerVersion (compiler lbi)
packageId | versionBranch ghc_vers >= [6,4]
= showPackageId (package pkg_descr)
| otherwise = pkgName (package pkg_descr)
ghcArgs =
pkg_conf
++ ["-package-name", packageId ]
++ constructGHCCmdLine lbi libBi libTargetDir verbosity
++ (libModules pkg_descr)
ghcArgsProf = ghcArgs
++ ["-prof",
"-hisuf", "p_hi",
"-osuf", "p_o"
]
++ ghcProfOptions libBi
ghcArgsShared = ghcArgs
++ ["-dynamic",
"-hisuf", "dyn_hi",
"-osuf", "dyn_o", "-fPIC"
]
++ ghcSharedOptions libBi
unless (null (libModules pkg_descr)) $
do ifVanillaLib forceVanillaLib (runGhcProg ghcArgs)
ifProfLib (runGhcProg ghcArgsProf)
ifSharedLib (runGhcProg ghcArgsShared)
unless (null (cSources libBi)) $ do
info verbosity "Building C Sources..."
sequence_ [do let (odir,args) = constructCcCmdLine lbi libBi pref
filename verbosity
createDirectoryIfMissingVerbose verbosity True odir
runGhcProg args
ifSharedLib (runGhcProg (args ++ ["-fPIC", "-osuf dyn_o"]))
| filename <- cSources libBi]
info verbosity "Linking..."
let cObjs = map (`replaceExtension` objExtension) (cSources libBi)
cSharedObjs = map (`replaceExtension` ("dyn_" ++ objExtension)) (cSources libBi)
libName = mkLibName pref (showPackageId (package pkg_descr))
profLibName = mkProfLibName pref (showPackageId (package pkg_descr))
sharedLibName = mkSharedLibName pref (showPackageId (package pkg_descr)) (compilerId (compiler lbi))
ghciLibName = mkGHCiLibName pref (showPackageId (package pkg_descr))
stubObjs <- sequence [moduleToFilePath [libTargetDir] (x ++"_stub") [objExtension]
| x <- libModules pkg_descr ] >>= return . concat
stubProfObjs <- sequence [moduleToFilePath [libTargetDir] (x ++"_stub") ["p_" ++ objExtension]
| x <- libModules pkg_descr ] >>= return . concat
stubSharedObjs <- sequence [moduleToFilePath [libTargetDir] (x ++"_stub") ["dyn_" ++ objExtension]
| x <- libModules pkg_descr ] >>= return . concat
hObjs <- getHaskellObjects pkg_descr libBi lbi
pref objExtension True
hProfObjs <-
if (withProfLib lbi)
then getHaskellObjects pkg_descr libBi lbi
pref ("p_" ++ objExtension) True
else return []
hSharedObjs <-
if (withSharedLib lbi)
then getHaskellObjects pkg_descr libBi lbi
pref ("dyn_" ++ objExtension) False
else return []
unless (null hObjs && null cObjs && null stubObjs) $ do
Try.try (removeFile libName)
Try.try (removeFile profLibName)
Try.try (removeFile sharedLibName)
Try.try (removeFile ghciLibName)
let arVerbosity | verbosity >= deafening = "v"
| verbosity >= normal = ""
| otherwise = "c"
arArgs = ["q"++ arVerbosity]
++ [libName]
arObjArgs =
hObjs
++ map (pref </>) cObjs
++ stubObjs
arProfArgs = ["q"++ arVerbosity]
++ [profLibName]
arProfObjArgs =
hProfObjs
++ map (pref </>) cObjs
++ stubProfObjs
ldArgs = ["-r"]
++ ["-o", ghciLibName <.> "tmp"]
ldObjArgs =
hObjs
++ map (pref </>) cObjs
++ stubObjs
ghcSharedObjArgs =
hSharedObjs
++ map (pref </>) cSharedObjs
++ stubSharedObjs
ghcSharedLinkArgs =
[ "-shared",
"-dynamic",
"-o", sharedLibName ]
++ ghcSharedObjArgs
++ ["-package-name", packageId ]
++ (concat [ ["-package", showPackageId pkg] | pkg <- packageDeps lbi ])
++ ["-l"++extraLib | extraLib <- extraLibs libBi]
++ ["-L"++extraLibDir | extraLibDir <- extraLibDirs libBi]
runLd ldLibName args = do
exists <- doesFileExist ldLibName
rawSystemProgramConf verbosity ldProgram (withPrograms lbi)
(args ++ if exists then [ldLibName] else [])
renameFile (ldLibName <.> "tmp") ldLibName
runAr = rawSystemProgramConf verbosity arProgram (withPrograms lbi)
maxCommandLineSize = 2048
ifVanillaLib False $ xargs maxCommandLineSize
runAr arArgs arObjArgs
ifProfLib $ xargs maxCommandLineSize
runAr arProfArgs arProfObjArgs
ifGHCiLib $ xargs maxCommandLineSize
(runLd ghciLibName) ldArgs ldObjArgs
ifSharedLib $ runGhcProg ghcSharedLinkArgs
withExe pkg_descr $ \ (Executable exeName' modPath exeBi) -> do
info verbosity $ "Building executable: " ++ exeName' ++ "..."
let exeNameReal = exeName' <.>
(if null $ takeExtension exeName' then exeExtension else "")
let targetDir = pref </> exeName'
let exeDir = targetDir </> (exeName' ++ "-tmp")
createDirectoryIfMissingVerbose verbosity True targetDir
createDirectoryIfMissingVerbose verbosity True exeDir
smartCopySources verbosity (hsSourceDirs exeBi)
exeDir (otherModules exeBi) ["hi-boot"] False False
unless (null (cSources exeBi)) $ do
info verbosity "Building C Sources."
sequence_ [do let (odir,args) = constructCcCmdLine lbi exeBi
exeDir filename verbosity
createDirectoryIfMissingVerbose verbosity True odir
runGhcProg args
| filename <- cSources exeBi]
srcMainFile <- findFile (exeDir : hsSourceDirs exeBi) modPath
let cObjs = map (`replaceExtension` objExtension) (cSources exeBi)
let binArgs linkExe profExe =
pkg_conf
++ (if linkExe
then ["-o", targetDir </> exeNameReal]
else ["-c"])
++ constructGHCCmdLine lbi exeBi exeDir verbosity
++ [exeDir </> x | x <- cObjs]
++ [srcMainFile]
++ ldOptions exeBi
++ ["-l"++lib | lib <- extraLibs exeBi]
++ ["-L"++libDir | libDir <- extraLibDirs exeBi]
++ concat [["-framework", f] | f <- frameworks exeBi]
++ if profExe
then ["-prof",
"-hisuf", "p_hi",
"-osuf", "p_o"
] ++ ghcProfOptions exeBi
else []
when (withProfExe lbi && TemplateHaskell `elem` extensions exeBi)
(runGhcProg (binArgs False False))
runGhcProg (binArgs True (withProfExe lbi))
getHaskellObjects :: PackageDescription -> BuildInfo -> LocalBuildInfo
-> FilePath -> String -> Bool -> IO [FilePath]
getHaskellObjects pkg_descr _ lbi pref wanted_obj_ext allow_split_objs
| splitObjs lbi && allow_split_objs = do
let dirs = [ pref </> (dotToSep x ++ "_split")
| x <- libModules pkg_descr ]
objss <- mapM getDirectoryContents dirs
let objs = [ dir </> obj
| (objs',dir) <- zip objss dirs, obj <- objs',
let obj_ext = takeExtension obj,
'.':wanted_obj_ext == obj_ext ]
return objs
| otherwise =
return [ pref </> dotToSep x <.> wanted_obj_ext
| x <- libModules pkg_descr ]
constructGHCCmdLine
:: LocalBuildInfo
-> BuildInfo
-> FilePath
-> Verbosity
-> [String]
constructGHCCmdLine lbi bi odir verbosity =
["--make"]
++ ghcVerbosityOptions verbosity
++ ghcOptions lbi bi odir
ghcVerbosityOptions :: Verbosity -> [String]
ghcVerbosityOptions verbosity
| verbosity >= deafening = ["-v"]
| verbosity >= normal = []
| otherwise = ["-w", "-v0"]
ghcOptions :: LocalBuildInfo -> BuildInfo -> FilePath -> [String]
ghcOptions lbi bi odir
= (if compilerVersion c > Version [6,4] []
then ["-hide-all-packages"]
else [])
++ (if splitObjs lbi then ["-split-objs"] else [])
++ ["-i"]
++ ["-i" ++ autogenModulesDir lbi]
++ ["-i" ++ odir]
++ ["-i" ++ l | l <- nub (hsSourceDirs bi)]
++ ["-I" ++ odir]
++ ["-I" ++ dir | dir <- includeDirs bi]
++ ["-optP" ++ opt | opt <- cppOptions bi]
++ ["-optc" ++ opt | opt <- ccOptions bi]
++ [ "-#include \"" ++ inc ++ "\"" | inc <- includes bi ]
++ [ "-odir", odir, "-hidir", odir ]
++ (if compilerVersion c >= Version [6,8] []
then ["-stubdir", odir] else [])
++ (concat [ ["-package", showPackageId pkg] | pkg <- packageDeps lbi ])
++ (if withOptimization lbi then ["-O"] else [])
++ hcOptions GHC (options bi)
++ extensionsToFlags c (extensions bi)
where c = compiler lbi
constructCcCmdLine :: LocalBuildInfo -> BuildInfo -> FilePath
-> FilePath -> Verbosity -> (FilePath,[String])
constructCcCmdLine lbi bi pref filename verbosity
= let odir | compilerVersion (compiler lbi) >= Version [6,4,1] [] = pref
| otherwise = pref </> takeDirectory filename
in
(odir,
ghcCcOptions lbi bi odir
++ (if verbosity > deafening then ["-v"] else [])
++ ["-c",filename])
ghcCcOptions :: LocalBuildInfo -> BuildInfo -> FilePath -> [String]
ghcCcOptions lbi bi odir
= ["-I" ++ dir | dir <- includeDirs bi]
++ concat [ ["-package", showPackageId pkg] | pkg <- packageDeps lbi ]
++ ["-optc" ++ opt | opt <- ccOptions bi]
++ (if withOptimization lbi then ["-optc-O2"] else [])
++ ["-odir", odir]
mkGHCiLibName :: FilePath
-> String
-> String
mkGHCiLibName pref lib = pref </> ("HS" ++ lib) <.> ".o"
makefile :: PackageDescription -> LocalBuildInfo -> MakefileFlags -> IO ()
makefile pkg_descr lbi flags = do
let file = case makefileFile flags of
Just f -> f
_otherwise -> "Makefile"
targetExists <- doesFileExist file
when targetExists $
die ("Not overwriting existing copy of " ++ file)
h <- openFile file WriteMode
let Just lib = library pkg_descr
bi = libBuildInfo lib
ghc_vers = compilerVersion (compiler lbi)
packageId | versionBranch ghc_vers >= [6,4]
= showPackageId (package pkg_descr)
| otherwise = pkgName (package pkg_descr)
(arProg, _) <- requireProgram (makefileVerbose flags) arProgram AnyVersion
(withPrograms lbi)
(ldProg, _) <- requireProgram (makefileVerbose flags) ldProgram AnyVersion
(withPrograms lbi)
let builddir = buildDir lbi
Just ghcProg = lookupProgram ghcProgram (withPrograms lbi)
let decls = [
("modules", unwords (exposedModules lib ++ otherModules bi)),
("GHC", programPath ghcProg),
("GHC_VERSION", (showVersion (compilerVersion (compiler lbi)))),
("WAYS", (if withProfLib lbi then "p " else "") ++ (if withSharedLib lbi then "dyn" else "")),
("odir", builddir),
("srcdir", case hsSourceDirs bi of
[one] -> one
_ -> error "makefile: can't cope with multiple hs-source-dirs yet, sorry"),
("package", packageId),
("GHC_OPTS", unwords (
["-package-name", packageId ]
++ ghcOptions lbi bi (buildDir lbi))),
("MAKEFILE", file),
("C_SRCS", unwords (cSources bi)),
("GHC_CC_OPTS", unwords (ghcCcOptions lbi bi (buildDir lbi))),
("GHCI_LIB", mkGHCiLibName builddir (showPackageId (package pkg_descr))),
("soext", dllExtension),
("LIB_LD_OPTS", unwords (["-package-name", packageId]
++ concat [ ["-package", showPackageId pkg] | pkg <- packageDeps lbi ]
++ ["-l"++libName | libName <- extraLibs bi]
++ ["-L"++libDir | libDir <- extraLibDirs bi])),
("AR", programPath arProg),
("LD", programPath ldProg ++ concat [" " ++ arg | arg <- programArgs ldProg ])
]
hPutStrLn h "# DO NOT EDIT! Automatically generated by Cabal\n"
hPutStrLn h (unlines (map (\(a,b)-> a ++ " = " ++ munge b) decls))
hPutStrLn h makefileTemplate
hClose h
where
munge "" = ""
munge ('#':s) = '\\':'#':munge s
munge ('\\':s) = '/':munge s
munge (c:s) = c : munge s
installExe :: Verbosity
-> FilePath
-> FilePath
-> PackageDescription
-> IO ()
installExe verbosity pref buildPref pkg_descr
= do createDirectoryIfMissingVerbose verbosity True pref
withExe pkg_descr $ \ (Executable e _ _) -> do
let exeFileName = e <.> exeExtension
copyFileVerbose verbosity (buildPref </> e </> exeFileName) (pref </> exeFileName)
installLib :: Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> FilePath
-> PackageDescription -> IO ()
installLib verbosity lbi pref dynPref buildPref
pd@PackageDescription{library=Just _,
package=p}
= do let programConf = withPrograms lbi
ifVanilla $ smartCopySources verbosity [buildPref] pref (libModules pd) ["hi"] True False
ifProf $ smartCopySources verbosity [buildPref] pref (libModules pd) ["p_hi"] True False
let libTargetLoc = mkLibName pref (showPackageId p)
profLibTargetLoc = mkProfLibName pref (showPackageId p)
libGHCiTargetLoc = mkGHCiLibName pref (showPackageId p)
sharedLibTargetLoc = mkSharedLibName dynPref (showPackageId p) (compilerId (compiler lbi))
ifVanilla $ copyFileVerbose verbosity (mkLibName buildPref (showPackageId p)) libTargetLoc
ifProf $ copyFileVerbose verbosity (mkProfLibName buildPref (showPackageId p)) profLibTargetLoc
ifGHCi $ copyFileVerbose verbosity (mkGHCiLibName buildPref (showPackageId p)) libGHCiTargetLoc
ifShared $ copyFileVerbose verbosity (mkSharedLibName buildPref (showPackageId p) (compilerId (compiler lbi))) sharedLibTargetLoc
case lookupProgram ranlibProgram programConf of
Just rl -> do ifVanilla $ rawSystemProgram verbosity rl [libTargetLoc]
ifProf $ rawSystemProgram verbosity rl [profLibTargetLoc]
Nothing -> case lookupProgram arProgram programConf of
Just ar -> do ifVanilla $ rawSystemProgram verbosity ar ["-s", libTargetLoc]
ifProf $ rawSystemProgram verbosity ar ["-s", profLibTargetLoc]
Nothing -> setupMessage verbosity "Warning: Unable to generate index for library (missing ranlib and ar)" pd
return ()
where ifVanilla action = when (withVanillaLib lbi) (action >> return ())
ifProf action = when (withProfLib lbi) (action >> return ())
ifGHCi action = when (withGHCiLib lbi) (action >> return ())
ifShared action = when (withSharedLib lbi) (action >> return ())
installLib _ _ _ _ _ PackageDescription{library=Nothing}
= die $ "Internal Error. installLibGHC called with no library."