Skip to content

Commit

Permalink
Add some support for libraries that make multiple .dll/.so/.a/... files
Browse files Browse the repository at this point in the history
Cabal doesn't know how to build them, but it does know how to install
and register them. In particular, this means that GHC's build system
can use Cabal to install them.
  • Loading branch information
Ian Lynagh committed Mar 12, 2013
1 parent 24bdc9b commit 8395c5d
Show file tree
Hide file tree
Showing 8 changed files with 143 additions and 74 deletions.
17 changes: 9 additions & 8 deletions Cabal/Distribution/Simple/BuildPaths.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,8 @@ import qualified Distribution.ModuleName as ModuleName
import Distribution.Compiler
( CompilerId(..) )
import Distribution.PackageDescription (PackageDescription)
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(buildDir))
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(buildDir), LibraryName(..) )
import Distribution.Simple.Setup (defaultDistPref)
import Distribution.Text
( display )
Expand Down Expand Up @@ -109,18 +110,18 @@ haddockName pkg_descr = display (packageName pkg_descr) <.> "haddock"
-- ---------------------------------------------------------------------------
-- Library file names

mkLibName :: PackageIdentifier -> String
mkLibName lib = "libHS" ++ display lib <.> "a"
mkLibName :: LibraryName -> String
mkLibName (LibraryName lib) = "lib" ++ lib <.> "a"

mkProfLibName :: PackageIdentifier -> String
mkProfLibName lib = "libHS" ++ display lib ++ "_p" <.> "a"
mkProfLibName :: LibraryName -> String
mkProfLibName (LibraryName lib) = "lib" ++ lib ++ "_p" <.> "a"

-- Implement proper name mangling for dynamical shared objects
-- libHS<packagename>-<compilerFlavour><compilerVersion>
-- e.g. libHSbase-2.1-ghc6.6.1.so
mkSharedLibName :: PackageIdentifier -> CompilerId -> String
mkSharedLibName lib (CompilerId compilerFlavor compilerVersion)
= "libHS" ++ display lib ++ "-" ++ comp <.> dllExtension
mkSharedLibName :: CompilerId -> LibraryName -> String
mkSharedLibName (CompilerId compilerFlavor compilerVersion) (LibraryName lib)
= "lib" ++ lib ++ "-" ++ comp <.> dllExtension
where comp = display compilerFlavor ++ display compilerVersion

-- ------------------------------------------------------------
Expand Down
38 changes: 27 additions & 11 deletions Cabal/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,8 @@ import Distribution.Simple.Setup
import Distribution.Simple.InstallDirs
( InstallDirs(..), defaultInstallDirs, combineInstallDirs )
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..), ComponentLocalBuildInfo(..)
( LocalBuildInfo(..), Component(..), ComponentLocalBuildInfo(..)
, LibraryName(..)
, absoluteInstallDirs, prefixRelativeInstallDirs, inplacePackageId
, ComponentName(..), showComponentName, pkgEnabledComponents
, componentBuildInfo, componentName, checkComponentsCyclic )
Expand Down Expand Up @@ -854,18 +855,33 @@ mkComponentsLocalBuildInfo pkg_descr internalPkgDeps externalPkgDeps =
-- needs. Note, this only works because we cannot yet depend on two
-- versions of the same package.
componentLocalBuildInfo component =
ComponentLocalBuildInfo {
componentPackageDeps =
if newPackageDepsBehaviour pkg_descr
then [ (installedPackageId pkg, packageId pkg)
| pkg <- selectSubset bi externalPkgDeps ]
++ [ (inplacePackageId pkgid, pkgid)
| pkgid <- selectSubset bi internalPkgDeps ]
else [ (installedPackageId pkg, packageId pkg)
| pkg <- externalPkgDeps ]
}
case component of
CLib _ ->
LibComponentLocalBuildInfo {
componentPackageDeps = cpds,
componentLibraries = [LibraryName ("HS" ++ display (package pkg_descr))]
}
CExe _ ->
ExeComponentLocalBuildInfo {
componentPackageDeps = cpds
}
CTest _ ->
TestComponentLocalBuildInfo {
componentPackageDeps = cpds
}
CBench _ ->
BenchComponentLocalBuildInfo {
componentPackageDeps = cpds
}
where
bi = componentBuildInfo component
cpds = if newPackageDepsBehaviour pkg_descr
then [ (installedPackageId pkg, packageId pkg)
| pkg <- selectSubset bi externalPkgDeps ]
++ [ (inplacePackageId pkgid, pkgid)
| pkgid <- selectSubset bi internalPkgDeps ]
else [ (installedPackageId pkg, packageId pkg)
| pkg <- externalPkgDeps ]

selectSubset :: Package pkg => BuildInfo -> [pkg] -> [pkg]
selectSubset bi pkgs =
Expand Down
53 changes: 30 additions & 23 deletions Cabal/Distribution/Simple/GHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ import Distribution.Simple.PackageIndex (PackageIndex)
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..), ComponentLocalBuildInfo(..)
, absoluteInstallDirs )
, LibraryName(..), absoluteInstallDirs )
import Distribution.Simple.InstallDirs hiding ( absoluteInstallDirs )
import Distribution.Simple.BuildPaths
import Distribution.Simple.Utils
Expand Down Expand Up @@ -621,6 +621,11 @@ substTopDir topDir ipo
buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo
-> Library -> ComponentLocalBuildInfo -> IO ()
buildLib verbosity pkg_descr lbi lib clbi = do
libName <- case componentLibraries clbi of
[libName] -> return libName
[] -> die "No library name found when building library"
_ -> die "Multiple library names found when building library"

let pref = buildDir lbi
pkgid = packageId pkg_descr
ifVanillaLib forceVanilla = when (forceVanilla || withVanillaLib lbi)
Expand Down Expand Up @@ -697,14 +702,13 @@ buildLib verbosity pkg_descr lbi lib clbi = do
info verbosity "Linking..."
let cObjs = map (`replaceExtension` objExtension) (cSources libBi)
cSharedObjs = map (`replaceExtension` ("dyn_" ++ objExtension)) (cSources libBi)
vanillaLibFilePath = libTargetDir </> mkLibName pkgid
profileLibFilePath = libTargetDir </> mkProfLibName pkgid
sharedLibFilePath = libTargetDir </> mkSharedLibName pkgid
(compilerId (compiler lbi))
ghciLibFilePath = libTargetDir </> mkGHCiLibName pkgid
cid = compilerId (compiler lbi)
vanillaLibFilePath = libTargetDir </> mkLibName libName
profileLibFilePath = libTargetDir </> mkProfLibName libName
sharedLibFilePath = libTargetDir </> mkSharedLibName cid libName
ghciLibFilePath = libTargetDir </> mkGHCiLibName libName
libInstallPath = libdir $ absoluteInstallDirs pkg_descr lbi NoCopyDest
sharedLibInstallPath = libInstallPath </> mkSharedLibName pkgid
(compilerId (compiler lbi))
sharedLibInstallPath = libInstallPath </> mkSharedLibName cid libName

stubObjs <- fmap catMaybes $ sequence
[ findFileWithExtension [objExtension] [libTargetDir]
Expand Down Expand Up @@ -1035,8 +1039,8 @@ componentCcGhcOptions verbosity lbi bi clbi pref filename =
| otherwise = pref </> takeDirectory filename
-- ghc 6.4.0 had a bug in -odir handling for C compilations.

mkGHCiLibName :: PackageIdentifier -> String
mkGHCiLibName lib = "HS" ++ display lib <.> "o"
mkGHCiLibName :: LibraryName -> String
mkGHCiLibName (LibraryName lib) = lib <.> "o"

-- -----------------------------------------------------------------------------
-- Installing
Expand Down Expand Up @@ -1087,8 +1091,9 @@ installLib :: Verbosity
-> FilePath -- ^Build location
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
installLib verbosity lbi targetDir dynlibTargetDir builtDir pkg lib = do
installLib verbosity lbi targetDir dynlibTargetDir builtDir pkg lib clbi = do
-- copy .hi files over:
let copyHelper installFun src dst n = do
createDirectoryIfMissingVerbose verbosity True dst
Expand All @@ -1103,22 +1108,24 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir pkg lib = do
ifShared $ copyModuleFiles "dyn_hi"

-- copy the built library files over:
ifVanilla $ copy builtDir targetDir vanillaLibName
ifProf $ copy builtDir targetDir profileLibName
ifGHCi $ copy builtDir targetDir ghciLibName
ifShared $ copyShared builtDir dynlibTargetDir sharedLibName
ifVanilla $ mapM_ (copy builtDir targetDir) vanillaLibNames
ifProf $ mapM_ (copy builtDir targetDir) profileLibNames
ifGHCi $ mapM_ (copy builtDir targetDir) ghciLibNames
ifShared $ mapM_ (copyShared builtDir dynlibTargetDir) sharedLibNames

-- run ranlib if necessary:
ifVanilla $ updateLibArchive verbosity lbi
(targetDir </> vanillaLibName)
ifProf $ updateLibArchive verbosity lbi
(targetDir </> profileLibName)
ifVanilla $ mapM_ (updateLibArchive verbosity lbi . (targetDir </>))
vanillaLibNames
ifProf $ mapM_ (updateLibArchive verbosity lbi . (targetDir </>))
profileLibNames

where
vanillaLibName = mkLibName pkgid
profileLibName = mkProfLibName pkgid
ghciLibName = mkGHCiLibName pkgid
sharedLibName = mkSharedLibName pkgid (compilerId (compiler lbi))
cid = compilerId (compiler lbi)
libNames = componentLibraries clbi
vanillaLibNames = map mkLibName libNames
profileLibNames = map mkProfLibName libNames
ghciLibNames = map mkGHCiLibName libNames
sharedLibNames = map (mkSharedLibName cid) libNames

pkgid = packageId pkg

Expand Down
9 changes: 4 additions & 5 deletions Cabal/Distribution/Simple/Install.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ import Distribution.PackageDescription (
import Distribution.Package (Package(..))
import Distribution.Simple.LocalBuildInfo (
LocalBuildInfo(..), InstallDirs(..), absoluteInstallDirs,
substPathTemplate)
substPathTemplate, withLibLBI)
import Distribution.Simple.BuildPaths (haddockName, haddockPref)
import Distribution.Simple.Utils
( createDirectoryIfMissingVerbose
Expand Down Expand Up @@ -156,11 +156,11 @@ install pkg_descr lbi flags = do
when (hasLibs pkg_descr) $ installIncludeFiles verbosity pkg_descr incPref

case compilerFlavor (compiler lbi) of
GHC -> do withLib pkg_descr $
GHC -> do withLibLBI pkg_descr lbi $
GHC.installLib verbosity lbi libPref dynlibPref buildPref pkg_descr
withExe pkg_descr $
GHC.installExe verbosity lbi installDirs buildPref (progPrefixPref, progSuffixPref) pkg_descr
LHC -> do withLib pkg_descr $
LHC -> do withLibLBI pkg_descr lbi $
LHC.installLib verbosity lbi libPref dynlibPref buildPref pkg_descr
withExe pkg_descr $
LHC.installExe verbosity lbi installDirs buildPref (progPrefixPref, progSuffixPref) pkg_descr
Expand All @@ -172,13 +172,12 @@ install pkg_descr lbi flags = do
let targetProgPref = progdir (absoluteInstallDirs pkg_descr lbi NoCopyDest)
let scratchPref = scratchDir lbi
Hugs.install verbosity lbi libPref progPref binPref targetProgPref scratchPref (progPrefixPref, progSuffixPref) pkg_descr
NHC -> do withLib pkg_descr $ NHC.installLib verbosity libPref buildPref (packageId pkg_descr)
NHC -> do withLibLBI pkg_descr lbi $ NHC.installLib verbosity libPref buildPref (packageId pkg_descr)
withExe pkg_descr $ NHC.installExe verbosity binPref buildPref (progPrefixPref, progSuffixPref)
UHC -> do withLib pkg_descr $ UHC.installLib verbosity lbi libPref dynlibPref buildPref pkg_descr
_ -> die $ "installing with "
++ display (compilerFlavor (compiler lbi))
++ " is not implemented"
return ()
-- register step should be performed by caller.

-- | Install the files listed in data-files
Expand Down
51 changes: 30 additions & 21 deletions Cabal/Distribution/Simple/LHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,8 @@ import Distribution.Simple.PackageIndex
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.ParseUtils ( ParseResult(..) )
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..), ComponentLocalBuildInfo(..) )
( LocalBuildInfo(..), ComponentLocalBuildInfo(..),
ComponentName(..), LibraryName(..) )
import Distribution.Simple.InstallDirs
import Distribution.Simple.BuildPaths
import Distribution.Simple.Utils
Expand Down Expand Up @@ -334,6 +335,11 @@ substTopDir topDir ipo
buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo
-> Library -> ComponentLocalBuildInfo -> IO ()
buildLib verbosity pkg_descr lbi lib clbi = do
libName <- case componentLibraries clbi of
[libName] -> return libName
[] -> die "No library name found when building library"
_ -> die "Multiple library names found when building library"

let pref = buildDir lbi
pkgid = packageId pkg_descr
runGhcProg = rawSystemProgramConf verbosity lhcProgram (withPrograms lbi)
Expand Down Expand Up @@ -387,11 +393,11 @@ buildLib verbosity pkg_descr lbi lib clbi = do
info verbosity "Linking..."
let cObjs = map (`replaceExtension` objExtension) (cSources libBi)
cSharedObjs = map (`replaceExtension` ("dyn_" ++ objExtension)) (cSources libBi)
vanillaLibFilePath = libTargetDir </> mkLibName pkgid
profileLibFilePath = libTargetDir </> mkProfLibName pkgid
sharedLibFilePath = libTargetDir </> mkSharedLibName pkgid
(compilerId (compiler lbi))
ghciLibFilePath = libTargetDir </> mkGHCiLibName pkgid
cid = compilerId (compiler lbi)
vanillaLibFilePath = libTargetDir </> mkLibName libName
profileLibFilePath = libTargetDir </> mkProfLibName libName
sharedLibFilePath = libTargetDir </> mkSharedLibName cid libName
ghciLibFilePath = libTargetDir </> mkGHCiLibName libName

stubObjs <- fmap catMaybes $ sequence
[ findFileWithExtension [objExtension] [libTargetDir]
Expand Down Expand Up @@ -697,8 +703,8 @@ ghcCcOptions lbi bi clbi odir
_ -> ["-optc-O2"])
++ ["-odir", odir]

mkGHCiLibName :: PackageIdentifier -> String
mkGHCiLibName lib = "HS" ++ display lib <.> "o"
mkGHCiLibName :: LibraryName -> String
mkGHCiLibName (LibraryName lib) = lib <.> "o"

-- -----------------------------------------------------------------------------
-- Installing
Expand Down Expand Up @@ -749,8 +755,9 @@ installLib :: Verbosity
-> FilePath -- ^Build location
-> PackageDescription
-> Library
-> ComponentLocalBuildInfo
-> IO ()
installLib verbosity lbi targetDir dynlibTargetDir builtDir pkg lib = do
installLib verbosity lbi targetDir dynlibTargetDir builtDir pkg lib clbi = do
-- copy .hi files over:
let copy src dst n = do
createDirectoryIfMissingVerbose verbosity True dst
Expand All @@ -764,22 +771,24 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir pkg lib = do
flip mapM_ hcrFiles $ \(srcBase, srcFile) -> runLhc ["--install-library", srcBase </> srcFile]

-- copy the built library files over:
ifVanilla $ copy builtDir targetDir vanillaLibName
ifProf $ copy builtDir targetDir profileLibName
ifGHCi $ copy builtDir targetDir ghciLibName
ifShared $ copy builtDir dynlibTargetDir sharedLibName
ifVanilla $ mapM_ (copy builtDir targetDir) vanillaLibNames
ifProf $ mapM_ (copy builtDir targetDir) profileLibNames
ifGHCi $ mapM_ (copy builtDir targetDir) ghciLibNames
ifShared $ mapM_ (copy builtDir dynlibTargetDir) sharedLibNames

-- run ranlib if necessary:
ifVanilla $ updateLibArchive verbosity lbi
(targetDir </> vanillaLibName)
ifProf $ updateLibArchive verbosity lbi
(targetDir </> profileLibName)
ifVanilla $ mapM_ (updateLibArchive verbosity lbi . (targetDir </>))
vanillaLibNames
ifProf $ mapM_ (updateLibArchive verbosity lbi . (targetDir </>))
profileLibNames

where
vanillaLibName = mkLibName pkgid
profileLibName = mkProfLibName pkgid
ghciLibName = mkGHCiLibName pkgid
sharedLibName = mkSharedLibName pkgid (compilerId (compiler lbi))
cid = compilerId (compiler lbi)
libNames = componentLibraries clbi
vanillaLibNames = map mkLibName libNames
profileLibNames = map mkProfLibName libNames
ghciLibNames = map mkGHCiLibName libNames
sharedLibNames = map (mkSharedLibName cid) libNames

pkgid = packageId pkg

Expand Down
29 changes: 28 additions & 1 deletion Cabal/Distribution/Simple/LocalBuildInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,7 @@ module Distribution.Simple.LocalBuildInfo (
ComponentName(..),
showComponentName,
ComponentLocalBuildInfo(..),
LibraryName(..),
foldComponent,
componentName,
componentBuildInfo,
Expand Down Expand Up @@ -199,7 +200,30 @@ showComponentName (CExeName name) = "executable '" ++ name ++ "'"
showComponentName (CTestName name) = "test suite '" ++ name ++ "'"
showComponentName (CBenchName name) = "benchmark '" ++ name ++ "'"

data ComponentLocalBuildInfo = ComponentLocalBuildInfo {
data ComponentLocalBuildInfo
= LibComponentLocalBuildInfo {
-- | Resolved internal and external package dependencies for this component.
-- The 'BuildInfo' specifies a set of build dependencies that must be
-- satisfied in terms of version ranges. This field fixes those dependencies
-- to the specific versions available on this machine for this compiler.
componentPackageDeps :: [(InstalledPackageId, PackageId)],
componentLibraries :: [LibraryName]
}
| ExeComponentLocalBuildInfo {
-- | Resolved internal and external package dependencies for this component.
-- The 'BuildInfo' specifies a set of build dependencies that must be
-- satisfied in terms of version ranges. This field fixes those dependencies
-- to the specific versions available on this machine for this compiler.
componentPackageDeps :: [(InstalledPackageId, PackageId)]
}
| TestComponentLocalBuildInfo {
-- | Resolved internal and external package dependencies for this component.
-- The 'BuildInfo' specifies a set of build dependencies that must be
-- satisfied in terms of version ranges. This field fixes those dependencies
-- to the specific versions available on this machine for this compiler.
componentPackageDeps :: [(InstalledPackageId, PackageId)]
}
| BenchComponentLocalBuildInfo {
-- | Resolved internal and external package dependencies for this component.
-- The 'BuildInfo' specifies a set of build dependencies that must be
-- satisfied in terms of version ranges. This field fixes those dependencies
Expand All @@ -219,6 +243,9 @@ foldComponent _ f _ _ (CExe exe) = f exe
foldComponent _ _ f _ (CTest tst) = f tst
foldComponent _ _ _ f (CBench bch) = f bch

data LibraryName = LibraryName String
deriving (Read, Show)

componentBuildInfo :: Component -> BuildInfo
componentBuildInfo =
foldComponent libBuildInfo buildInfo testBuildInfo benchmarkBuildInfo
Expand Down

0 comments on commit 8395c5d

Please sign in to comment.