diff --git a/Cabal/Distribution/InstalledPackageInfo.hs b/Cabal/Distribution/InstalledPackageInfo.hs index fcbc28295bde067de46d9783385350b8db7e72df..f86aee7b0b1db7417d1c0c92867f921145838331 100644 --- a/Cabal/Distribution/InstalledPackageInfo.hs +++ b/Cabal/Distribution/InstalledPackageInfo.hs @@ -28,6 +28,7 @@ module Distribution.InstalledPackageInfo ( InstalledPackageInfo_(..), InstalledPackageInfo, + libraryName, OriginalModule(..), ExposedModule(..), ParseResult(..), PError(..), PWarning, emptyInstalledPackageInfo, @@ -50,7 +51,8 @@ import Distribution.License ( License(..) ) import Distribution.Package ( PackageName(..), PackageIdentifier(..) , PackageId, InstalledPackageId(..) - , packageName, packageVersion, PackageKey(..) ) + , packageName, packageVersion, PackageKey(..) + , LibraryName(..) ) import qualified Distribution.Package as Package import Distribution.ModuleName ( ModuleName ) @@ -110,6 +112,9 @@ data InstalledPackageInfo_ m } deriving (Generic, Read, Show) +libraryName :: InstalledPackageInfo_ a -> LibraryName +libraryName ipi = Package.packageKeyLibraryName (sourcePackageId ipi) (packageKey ipi) + instance Binary m => Binary (InstalledPackageInfo_ m) instance Package.Package (InstalledPackageInfo_ str) where @@ -287,7 +292,7 @@ basicFieldDescrs = installedPackageId (\ipid pkg -> pkg{installedPackageId=ipid}) , simpleField "key" disp parse - packageKey (\ipid pkg -> pkg{packageKey=ipid}) + packageKey (\pk pkg -> pkg{packageKey=pk}) , simpleField "license" disp parseLicenseQ license (\l pkg -> pkg{license=l}) diff --git a/Cabal/Distribution/Package.hs b/Cabal/Distribution/Package.hs index ca0daf634a734a180007c7c3c1bfadbcd257254a..d2ca47db810039cb0faf9bc72d5d04687dc1117b 100644 --- a/Cabal/Distribution/Package.hs +++ b/Cabal/Distribution/Package.hs @@ -24,12 +24,17 @@ module Distribution.Package ( -- * Installed package identifiers InstalledPackageId(..), - -- * Package keys (used for linker symbols and library name) + -- * Package keys (used for linker symbols) PackageKey(..), mkPackageKey, packageKeyHash, packageKeyLibraryName, + -- * Library name (used for install path, package key) + LibraryName(..), + emptyLibraryName, + getHSLibraryName, + -- * Package source dependencies Dependency(..), thisPackageVersion, @@ -42,7 +47,6 @@ module Distribution.Package ( PackageInstalled(..), ) where -import Distribution.ModuleName ( ModuleName ) import Distribution.Version ( Version(..), VersionRange, anyVersion, thisVersion , notThisVersion, simplifyVersionRange ) @@ -53,12 +57,11 @@ import Distribution.Compat.ReadP ((<++)) import qualified Text.PrettyPrint as Disp import Control.DeepSeq (NFData(..)) -import Data.Ord ( comparing ) import Distribution.Compat.Binary (Binary) import qualified Data.Char as Char ( isDigit, isAlphaNum, isUpper, isLower, ord, chr ) import Data.Data ( Data ) -import Data.List ( intercalate, foldl', sortBy ) +import Data.List ( intercalate, foldl', sort ) import Data.Typeable ( Typeable ) import Data.Word ( Word64 ) import GHC.Fingerprint ( Fingerprint(..), fingerprintString ) @@ -140,50 +143,14 @@ instance Text InstalledPackageId where -- concept written explicity in Cabal files; on the other hand, a 'PackageKey' -- may contain, for example, information about the transitive dependency -- tree of a package. Why is this not an 'InstalledPackageId'? A 'PackageKey' --- affects the ABI because it is used for linker symbols; however, an --- 'InstalledPackageId' can be used to distinguish two ABI-compatible versions --- of a library. --- --- The key is defined to be a 128-bit MD5 hash, separated into two 64-bit --- components (the most significant component coming first) which are --- individually base-62 encoded (A-Z, a-z, 0-9). --- --- @ --- key ::= hash64 hash64 --- hash64 ::= [A-Za-z0-9]{11} --- @ --- --- The string that is hashed is specified as raw_key: --- --- @ --- raw_key ::= package_id "\n" --- holes_nl --- depends_nl --- package_id ::= package_name "-" package_version --- holes_nl ::= "" --- | hole_inst "\n" holes_nl --- hole_inst ::= modulename " " key ":" modulename --- depends_nl ::= "" --- | depend "\n" depends_nl --- depend ::= key --- @ +-- should be stable so that we can incrementally recompile after a source edit; +-- however, an 'InstalledPackageId' may change even with source. -- --- The holes list MUST be sorted by the first modulename; the depends list --- MUST be sorted by the key. holes describes the backing implementations of --- all holes in the package; depends describes all of the build-depends of --- a package. A package key MAY be used in holes even if it is not --- mentioned in depends: depends contains STRICTLY packages which are --- textually mentioned in the package description. --- --- The trailing newline is MANDATORY. --- --- There is also a variant of package key which is prefixed by a informational --- string. This is strictly for backwards compatibility with GHC 7.10. --- --- @ --- infokey ::= infostring "_" key --- infostring ::= [A-Za-z0-9-]+ --- @ +-- Package keys may be generated either by Cabal or GHC. In particular, +-- ordinary, "old-style" packages which don't use Backpack features can +-- have their package keys generated directly by Cabal and coincide with +-- 'LibraryName's. However, Backpack keys are generated by GHC may exhibit +-- more variation than a 'LibraryName'. -- data PackageKey -- | Modern package key which is a hash of the PackageId and the transitive @@ -207,19 +174,13 @@ fingerprintPackageKey (Fingerprint a b) = PackageKey Nothing a b -- immediate dependencies. mkPackageKey :: Bool -- are modern style package keys supported? -> PackageId - -> [PackageKey] -- dependencies - -> [(ModuleName, (PackageKey, ModuleName))] -- hole instantiations + -> [LibraryName] -- dependencies -> PackageKey -mkPackageKey True pid deps holes = +mkPackageKey True pid deps = fingerprintPackageKey . fingerprintString $ display pid ++ "\n" ++ - -- NB: packageKeyHash, NOT display - concat [ display m ++ " " ++ packageKeyHash p' - ++ ":" ++ display m' ++ "\n" - | (m, (p', m')) <- sortBy (comparing fst) holes] ++ - concat [ packageKeyHash d ++ "\n" - | d <- sortBy (comparing packageKeyHash) deps] -mkPackageKey False pid _ _ = OldPackageKey pid + concat [ display dep ++ "\n" | dep <- sort deps ] +mkPackageKey False pid _ = OldPackageKey pid -- The base-62 code is based off of 'locators' -- ((c) Operational Dynamics Consulting, BSD3 licensed) @@ -269,14 +230,18 @@ readBase62Fingerprint s = Fingerprint w1 w2 w1 = fromBase62 s1 w2 = fromBase62 (take word64Base62Len s2) +-- | Compute the hash (without a prefix) of a package key. In GHC 7.12 +-- this is equivalent to display. packageKeyHash :: PackageKey -> String packageKeyHash (PackageKey _ w1 w2) = toBase62 w1 ++ toBase62 w2 packageKeyHash (OldPackageKey pid) = display pid -packageKeyLibraryName :: PackageId -> PackageKey -> String +-- | Legacy function for GHC 7.10 to compute a LibraryName based on +-- the package key. +packageKeyLibraryName :: PackageId -> PackageKey -> LibraryName packageKeyLibraryName pid (PackageKey _ w1 w2) = - display pid ++ "-" ++ toBase62 w1 ++ toBase62 w2 -packageKeyLibraryName _ (OldPackageKey pid) = display pid + LibraryName (display pid ++ "-" ++ toBase62 w1 ++ toBase62 w2) +packageKeyLibraryName _ (OldPackageKey pid) = LibraryName (display pid) instance Text PackageKey where disp (PackageKey mb_prefix w1 w2) @@ -302,6 +267,38 @@ instance NFData PackageKey where rnf (PackageKey mb _ _) = rnf mb rnf (OldPackageKey pid) = rnf pid +-- ------------------------------------------------------------ +-- * Library names +-- ------------------------------------------------------------ + +-- | A library name consists of not only a source package +-- id ('PackageId') but also the library names of all textual +-- dependencies; thus, a library name uniquely identifies an +-- installed packages up to the dependency resolution done by Cabal. +-- Create using 'packageKeyLibraryName'. Library names are opaque, +-- Cabal defined strings. +newtype LibraryName + = LibraryName String + deriving (Generic, Read, Show, Eq, Ord, Typeable, Data) + +instance Binary LibraryName + +-- | Default library name for when it is not known. +emptyLibraryName :: LibraryName +emptyLibraryName = LibraryName "" + +-- | Returns library name prefixed with HS, suitable for filenames +getHSLibraryName :: LibraryName -> String +getHSLibraryName (LibraryName s) = "HS" ++ s + +instance Text LibraryName where + disp (LibraryName s) = Disp.text s + parse = LibraryName `fmap` Parse.munch1 hash_char + where hash_char c = Char.isAlphaNum c || c `elem` "-_." + +instance NFData LibraryName where + rnf (LibraryName s) = rnf s + -- ------------------------------------------------------------ -- * Package source dependencies -- ------------------------------------------------------------ diff --git a/Cabal/Distribution/Simple/Bench.hs b/Cabal/Distribution/Simple/Bench.hs index f6c90be16598411c993c9401939d9e0a80169bb5..aceb2380bbdd980edbd89647adf947209b7007e2 100644 --- a/Cabal/Distribution/Simple/Bench.hs +++ b/Cabal/Distribution/Simple/Bench.hs @@ -24,7 +24,7 @@ import Distribution.Simple.InstallDirs ( fromPathTemplate, initialPathTemplateEnv, PathTemplateVariable(..) , substPathTemplate , toPathTemplate, PathTemplate ) import qualified Distribution.Simple.LocalBuildInfo as LBI - ( LocalBuildInfo(..) ) + ( LocalBuildInfo(..), localLibraryName ) import Distribution.Simple.Setup ( BenchmarkFlags(..), fromFlag ) import Distribution.Simple.UserHooks ( Args ) import Distribution.Simple.Utils ( die, notice, rawSystemExitCode ) @@ -123,6 +123,6 @@ benchOption pkg_descr lbi bm template = fromPathTemplate $ substPathTemplate env template where env = initialPathTemplateEnv - (PD.package pkg_descr) (LBI.pkgKey lbi) + (PD.package pkg_descr) (LBI.localLibraryName lbi) (compilerInfo $ LBI.compiler lbi) (LBI.hostPlatform lbi) ++ [(BenchmarkNameVar, toPathTemplate $ PD.benchmarkName bm)] diff --git a/Cabal/Distribution/Simple/Build.hs b/Cabal/Distribution/Simple/Build.hs index 1db658b8bd13514c07dbd08c024b97d1ea524743..ea68988492669ef3df971347230431c927cf1b52 100644 --- a/Cabal/Distribution/Simple/Build.hs +++ b/Cabal/Distribution/Simple/Build.hs @@ -35,10 +35,11 @@ import qualified Distribution.Simple.Build.PathsModule as Build.PathsModule import Distribution.Package ( Package(..), PackageName(..), PackageIdentifier(..) - , Dependency(..), thisPackageVersion, mkPackageKey, packageName ) + , Dependency(..), thisPackageVersion, PackageKey(..), packageName + , LibraryName(..) ) import Distribution.Simple.Compiler ( Compiler, CompilerFlavor(..), compilerFlavor - , PackageDB(..), PackageDBStack, packageKeySupported ) + , PackageDB(..), PackageDBStack ) import Distribution.PackageDescription ( PackageDescription(..), BuildInfo(..), Library(..), Executable(..) , TestSuite(..), TestSuiteInterface(..), Benchmark(..) @@ -54,13 +55,13 @@ import Distribution.Simple.BuildTarget import Distribution.Simple.PreProcess ( preprocessComponent, preprocessExtras, PPSuffixHandler ) import Distribution.Simple.LocalBuildInfo - ( LocalBuildInfo(compiler, buildDir, withPackageDB, withPrograms, pkgKey) + ( LocalBuildInfo(compiler, buildDir, withPackageDB, withPrograms) , Component(..), componentName, getComponent, componentBuildInfo , ComponentLocalBuildInfo(..), pkgEnabledComponents , withComponentsInBuildOrder, componentsInBuildOrder , ComponentName(..), showComponentName , ComponentDisabledReason(..), componentDisabledReason - , inplacePackageId, LibraryName(..) ) + , inplacePackageId ) import Distribution.Simple.Program.Types import Distribution.Simple.Program.Db import qualified Distribution.Simple.Program.HcPkg as HcPkg @@ -392,7 +393,7 @@ testSuiteLibV09AsLibAndExe :: PackageDescription testSuiteLibV09AsLibAndExe pkg_descr test@TestSuite { testInterface = TestSuiteLibV09 _ m } clbi lbi distPref pwd = - (pkg, lib, libClbi, lbi', ipi, exe, exeClbi) + (pkg, lib, libClbi, lbi, ipi, exe, exeClbi) where bi = testBuildInfo test lib = Library { @@ -406,8 +407,9 @@ testSuiteLibV09AsLibAndExe pkg_descr libClbi = LibComponentLocalBuildInfo { componentPackageDeps = componentPackageDeps clbi , componentPackageRenaming = componentPackageRenaming clbi - , componentLibraries = [LibraryName (testName test)] + , componentLibraryName = LibraryName "test" , componentExposedModules = [IPI.ExposedModule m Nothing Nothing] + , componentPackageKey = OldPackageKey (PackageIdentifier (PackageName (testName test)) (pkgVersion (package pkg_descr))) } pkg = pkg_descr { package = (package pkg_descr) { @@ -418,16 +420,8 @@ testSuiteLibV09AsLibAndExe pkg_descr , testSuites = [] , library = Just lib } - -- Hack to make the library compile with the right package key. - -- Probably the "right" way to do this is move this information to - -- the ComponentLocalBuildInfo, but it seems odd that a single package - -- can define multiple actual packages. - lbi' = lbi { - pkgKey = mkPackageKey (packageKeySupported (compiler lbi)) - (package pkg) [] [] - } ipkgid = inplacePackageId (packageId pkg) - ipi = inplaceInstalledPackageInfo pwd distPref pkg ipkgid lib lbi' libClbi + ipi = inplaceInstalledPackageInfo pwd distPref pkg ipkgid lib lbi libClbi testDir = buildDir lbi </> stubName test </> stubName test ++ "-tmp" testLibDep = thisPackageVersion $ package pkg diff --git a/Cabal/Distribution/Simple/Build/Macros.hs b/Cabal/Distribution/Simple/Build/Macros.hs index cdb552ded7e3ebb43e543ebb2e5a0112d4b2cb6f..f0429cd47f4c734fb8b83e904013cc1138c8c3fe 100644 --- a/Cabal/Distribution/Simple/Build/Macros.hs +++ b/Cabal/Distribution/Simple/Build/Macros.hs @@ -33,7 +33,7 @@ import Distribution.PackageDescription import Distribution.Simple.Compiler ( packageKeySupported ) import Distribution.Simple.LocalBuildInfo - ( LocalBuildInfo(compiler, pkgKey, withPrograms), externalPackageDeps ) + ( LocalBuildInfo(compiler, withPrograms), externalPackageDeps, localPackageKey ) import Distribution.Simple.Program.Db ( configuredPrograms ) import Distribution.Simple.Program.Types @@ -97,11 +97,12 @@ generateMacros prefix name version = (major1:major2:minor:_) = map show (versionBranch version ++ repeat 0) -- | Generate the @CURRENT_PACKAGE_KEY@ definition for the package key --- of the current package, if supported by the compiler +-- of the current package, if supported by the compiler. +-- NB: this only makes sense for definite packages. generatePackageKeyMacro :: LocalBuildInfo -> String generatePackageKeyMacro lbi | packageKeySupported (compiler lbi) = - "#define CURRENT_PACKAGE_KEY \"" ++ display (pkgKey lbi) ++ "\"\n\n" + "#define CURRENT_PACKAGE_KEY \"" ++ display (localPackageKey lbi) ++ "\"\n\n" | otherwise = "" fixchar :: Char -> Char diff --git a/Cabal/Distribution/Simple/BuildPaths.hs b/Cabal/Distribution/Simple/BuildPaths.hs index 7b95ff728830872430dfad503b64880fb4c1dd92..4ed5790f817b1d12aec09ba9a84b472b6d2067b3 100644 --- a/Cabal/Distribution/Simple/BuildPaths.hs +++ b/Cabal/Distribution/Simple/BuildPaths.hs @@ -34,14 +34,14 @@ module Distribution.Simple.BuildPaths ( import System.FilePath ((</>), (<.>)) import Distribution.Package - ( packageName ) + ( packageName, LibraryName, getHSLibraryName ) import Distribution.ModuleName (ModuleName) import qualified Distribution.ModuleName as ModuleName import Distribution.Compiler ( CompilerId(..) ) import Distribution.PackageDescription (PackageDescription) import Distribution.Simple.LocalBuildInfo - ( LocalBuildInfo(buildDir), LibraryName(..) ) + ( LocalBuildInfo(buildDir) ) import Distribution.Simple.Setup (defaultDistPref) import Distribution.Text ( display ) @@ -82,17 +82,17 @@ haddockName pkg_descr = display (packageName pkg_descr) <.> "haddock" -- Library file names mkLibName :: LibraryName -> String -mkLibName (LibraryName lib) = "lib" ++ lib <.> "a" +mkLibName lib = "lib" ++ getHSLibraryName lib <.> "a" mkProfLibName :: LibraryName -> String -mkProfLibName (LibraryName lib) = "lib" ++ lib ++ "_p" <.> "a" +mkProfLibName lib = "lib" ++ getHSLibraryName 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 :: CompilerId -> LibraryName -> String -mkSharedLibName (CompilerId compilerFlavor compilerVersion) (LibraryName lib) - = "lib" ++ lib ++ "-" ++ comp <.> dllExtension +mkSharedLibName (CompilerId compilerFlavor compilerVersion) lib + = "lib" ++ getHSLibraryName lib ++ "-" ++ comp <.> dllExtension where comp = display compilerFlavor ++ display compilerVersion -- ------------------------------------------------------------ diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs index 861f8df00aebe8c2ef07a89613eb40ef7b316944..1b941bf08c2d51948bd24baaa11b794b4d1b1ce2 100644 --- a/Cabal/Distribution/Simple/Configure.hs +++ b/Cabal/Distribution/Simple/Configure.hs @@ -62,7 +62,7 @@ import Distribution.Package , packageName, packageVersion, Package(..) , Dependency(Dependency), simplifyDependency , InstalledPackageId(..), thisPackageVersion - , mkPackageKey, PackageKey(..), packageKeyLibraryName ) + , mkPackageKey, packageKeyLibraryName ) import qualified Distribution.InstalledPackageInfo as Installed import Distribution.InstalledPackageInfo (InstalledPackageInfo, emptyInstalledPackageInfo) import qualified Distribution.Simple.PackageIndex as PackageIndex @@ -94,7 +94,6 @@ import Distribution.Simple.InstallDirs ( InstallDirs(..), defaultInstallDirs, combineInstallDirs ) import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..), Component(..), ComponentLocalBuildInfo(..) - , LibraryName(..) , absoluteInstallDirs, prefixRelativeInstallDirs, inplacePackageId , ComponentName(..), showComponentName, pkgEnabledComponents , componentBuildInfo, componentName, checkComponentsCyclic ) @@ -564,27 +563,6 @@ configure (pkg_descr0, pbi) cfg | (name, uses) <- inconsistencies , (pkg, ver) <- uses ] - -- Calculate the package key. We're going to store it in LocalBuildInfo - -- canonically, but ComponentsLocalBuildInfo also needs to know about it - -- XXX Do we need the internal deps? - -- NB: does *not* include holeDeps! - let pkg_key = mkPackageKey (packageKeySupported comp) - (package pkg_descr) - (map Installed.packageKey externalPkgDeps) - (map (\(k,(p,m)) -> (k,(Installed.packageKey p,m))) hole_insts) - - -- internal component graph - buildComponents <- - case mkComponentsGraph pkg_descr internalPkgDeps of - Left componentCycle -> reportComponentCycle componentCycle - Right components -> - case mkComponentsLocalBuildInfo packageDependsIndex pkg_descr - internalPkgDeps externalPkgDeps holeDeps - (Map.fromList hole_insts) - pkg_key components of - Left problems -> reportModuleReexportProblems problems - Right components' -> return components' - -- installation directories defaultDirs <- defaultInstallDirs flavor userInstall (hasLibs pkg_descr) let installDirs = combineInstallDirs fromFlagOrDefault @@ -629,6 +607,16 @@ configure (pkg_descr0, pbi) cfg (pkg_descr', programsConfig''') <- configurePkgconfigPackages verbosity pkg_descr programsConfig'' + -- internal component graph + buildComponents <- + case mkComponentsGraph pkg_descr internalPkgDeps of + Left componentCycle -> reportComponentCycle componentCycle + Right components -> + mkComponentsLocalBuildInfo comp packageDependsIndex pkg_descr + internalPkgDeps externalPkgDeps holeDeps + (Map.fromList hole_insts) + components + split_objs <- if not (fromFlag $ configSplitObjs cfg) then return False @@ -726,7 +714,6 @@ configure (pkg_descr0, pbi) cfg installedPkgs = packageDependsIndex, pkgDescrFile = Nothing, localPkgDescr = pkg_descr', - pkgKey = pkg_key, instantiatedWith = hole_insts, withPrograms = programsConfig''', withVanillaLib = fromFlag $ configVanillaLib cfg, @@ -1299,20 +1286,19 @@ reportComponentCycle cnames = [ "'" ++ showComponentName cname ++ "'" | cname <- cnames ++ [head cnames] ] -mkComponentsLocalBuildInfo :: InstalledPackageIndex +mkComponentsLocalBuildInfo :: Compiler + -> InstalledPackageIndex -> PackageDescription -> [PackageId] -- internal package deps -> [InstalledPackageInfo] -- external package deps -> [InstalledPackageInfo] -- hole package deps -> Map ModuleName (InstalledPackageInfo, ModuleName) - -> PackageKey -> [(Component, [ComponentName])] - -> Either [(ModuleReexport, String)] -- errors - [(ComponentName, ComponentLocalBuildInfo, - [ComponentName])] -- ok -mkComponentsLocalBuildInfo installedPackages pkg_descr + -> IO [(ComponentName, ComponentLocalBuildInfo, + [ComponentName])] +mkComponentsLocalBuildInfo comp installedPackages pkg_descr internalPkgDeps externalPkgDeps holePkgDeps hole_insts - pkg_key graph = + graph = sequence [ do clbi <- componentLocalBuildInfo c return (componentName c, clbi, cdeps) @@ -1333,12 +1319,24 @@ mkComponentsLocalBuildInfo installedPackages pkg_descr (Installed.installedPackageId pkg) m) (Map.lookup n hole_insts))) (PD.exposedSignatures lib) - reexports <- resolveModuleReexports installedPackages - (packageId pkg_descr) - externalPkgDeps lib + let mb_reexports = resolveModuleReexports installedPackages + (packageId pkg_descr) + externalPkgDeps lib + reexports <- case mb_reexports of + Left problems -> reportModuleReexportProblems problems + Right r -> return r + + -- Calculate the version hash and package key. + let externalPkgs = selectSubset bi externalPkgDeps + pkg_key = mkPackageKey (packageKeySupported comp) + (package pkg_descr) + (map Installed.libraryName externalPkgs) + version_hash = packageKeyLibraryName (package pkg_descr) pkg_key + return LibComponentLocalBuildInfo { componentPackageDeps = cpds, - componentLibraries = [ LibraryName ("HS" ++ packageKeyLibraryName (package pkg_descr) pkg_key) ], + componentPackageKey = pkg_key, + componentLibraryName = version_hash, componentPackageRenaming = cprns, componentExposedModules = exports ++ reexports ++ esigs } @@ -1366,8 +1364,6 @@ mkComponentsLocalBuildInfo installedPackages pkg_descr | pkg <- selectSubset bi externalPkgDeps ] ++ [ (inplacePackageId pkgid, pkgid) | pkgid <- selectSubset bi internalPkgDeps ] - ++ [ (Installed.installedPackageId pkg, packageId pkg) - | pkg <- holePkgDeps ] else [ (Installed.installedPackageId pkg, packageId pkg) | pkg <- externalPkgDeps ] cprns = if newPackageDepsBehaviour pkg_descr diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs index a4acf95df3a2ab03a5a237d562c885ef0228d22c..6a6621003bb060750659fa53039478d8e5437704 100644 --- a/Cabal/Distribution/Simple/GHC.hs +++ b/Cabal/Distribution/Simple/GHC.hs @@ -413,12 +413,8 @@ buildOrReplLib :: Bool -> Verbosity -> Cabal.Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () buildOrReplLib forRepl verbosity numJobs 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 libTargetDir = buildDir lbi + let libName = componentLibraryName clbi + libTargetDir = buildDir lbi whenVanillaLib forceVanilla = when (forceVanilla || withVanillaLib lbi) whenProfLib = when (withProfLib lbi) @@ -430,8 +426,6 @@ buildOrReplLib forRepl verbosity numJobs pkg_descr lbi lib clbi = do ghcVersion = compilerVersion comp implInfo = getImplInfo comp (Platform _hostArch hostOS) = hostPlatform lbi - hole_insts = map (\(k,(p,n)) -> (k, (InstalledPackageInfo.packageKey p,n))) - (instantiatedWith lbi) (ghcProg, _) <- requireProgram verbosity ghcProgram (withPrograms lbi) let runGhcProg = runGHC verbosity ghcProg comp @@ -465,8 +459,6 @@ buildOrReplLib forRepl verbosity numJobs pkg_descr lbi lib clbi = do vanillaOpts = baseOpts `mappend` mempty { ghcOptMode = toFlag GhcModeMake, ghcOptNumJobs = numJobs, - ghcOptPackageKey = toFlag (pkgKey lbi), - ghcOptSigOf = hole_insts, ghcOptInputModules = toNubListR $ libModules lib, ghcOptHPCDir = hpcdir Hpc.Vanilla } @@ -658,7 +650,6 @@ buildOrReplLib forRepl verbosity numJobs pkg_descr lbi lib clbi = do && ghcVersion < Version [7,8] []) then toFlag sharedLibInstallPath else mempty, - ghcOptPackageKey = toFlag (pkgKey lbi), ghcOptNoAutoLinkPackages = toFlag True, ghcOptPackageDBs = withPackageDB lbi, ghcOptPackages = toNubListR $ @@ -969,7 +960,6 @@ libAbiHash verbosity _pkg_descr lbi lib clbi = do (componentGhcOptions verbosity lbi libBi clbi (buildDir lbi)) `mappend` mempty { ghcOptMode = toFlag GhcModeAbiHash, - ghcOptPackageKey = toFlag (pkgKey lbi), ghcOptInputModules = toNubListR $ exposedModules lib } sharedArgs = vanillaArgs `mappend` mempty { @@ -1056,10 +1046,10 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir _pkg lib clbi = do whenShared $ copyModuleFiles "dyn_hi" -- copy the built library files over: - whenVanilla $ mapM_ (installOrdinary builtDir targetDir) vanillaLibNames - whenProf $ mapM_ (installOrdinary builtDir targetDir) profileLibNames - whenGHCi $ mapM_ (installOrdinary builtDir targetDir) ghciLibNames - whenShared $ mapM_ (installShared builtDir dynlibTargetDir) sharedLibNames + whenVanilla $ installOrdinary builtDir targetDir vanillaLibName + whenProf $ installOrdinary builtDir targetDir profileLibName + whenGHCi $ installOrdinary builtDir targetDir ghciLibName + whenShared $ installShared builtDir dynlibTargetDir sharedLibName where install isShared srcDir dstDir name = do @@ -1080,11 +1070,11 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir _pkg lib clbi = do >>= installOrdinaryFiles verbosity targetDir cid = compilerId (compiler lbi) - libNames = componentLibraries clbi - vanillaLibNames = map mkLibName libNames - profileLibNames = map mkProfLibName libNames - ghciLibNames = map Internal.mkGHCiLibName libNames - sharedLibNames = map (mkSharedLibName cid) libNames + libName = componentLibraryName clbi + vanillaLibName = mkLibName libName + profileLibName = mkProfLibName libName + ghciLibName = Internal.mkGHCiLibName libName + sharedLibName = (mkSharedLibName cid) libName hasLib = not $ null (libModules lib) && null (cSources (libBuildInfo lib)) diff --git a/Cabal/Distribution/Simple/GHC/Internal.hs b/Cabal/Distribution/Simple/GHC/Internal.hs index ee1f6039577fa7513e8c8a5c238069e5a82a034c..b53da0e6296735b730bc9769733beb8341215ca2 100644 --- a/Cabal/Distribution/Simple/GHC/Internal.hs +++ b/Cabal/Distribution/Simple/GHC/Internal.hs @@ -31,7 +31,8 @@ module Distribution.Simple.GHC.Internal ( import Distribution.Simple.GHC.ImplInfo ( GhcImplInfo (..) ) import Distribution.Package - ( InstalledPackageId, PackageId ) + ( InstalledPackageId, PackageId, LibraryName + , getHSLibraryName ) import Distribution.InstalledPackageInfo ( InstalledPackageInfo ) import qualified Distribution.InstalledPackageInfo as InstalledPackageInfo @@ -56,8 +57,7 @@ import Distribution.Simple.Program , getProgramOutput ) import Distribution.Simple.Program.Types ( suppressOverrideArgs ) import Distribution.Simple.LocalBuildInfo - ( LocalBuildInfo(..), ComponentLocalBuildInfo(..) - , LibraryName(..) ) + ( LocalBuildInfo(..), ComponentLocalBuildInfo(..) ) import Distribution.Simple.Utils import Distribution.Simple.BuildPaths import Distribution.System ( buildOS, OS(..), Platform, platformFromTriple ) @@ -374,6 +374,10 @@ componentGhcOptions verbosity lbi bi clbi odir = ghcOptVerbosity = toFlag verbosity, ghcOptHideAllPackages = toFlag True, ghcOptCabal = toFlag True, + ghcOptPackageKey = case clbi of + LibComponentLocalBuildInfo { componentPackageKey = pk } -> toFlag pk + _ -> mempty, + ghcOptSigOf = hole_insts, ghcOptPackageDBs = withPackageDB lbi, ghcOptPackages = toNubListR $ mkGhcOptPackages clbi, ghcOptSplitObjs = toFlag (splitObjs lbi), @@ -409,6 +413,9 @@ componentGhcOptions verbosity lbi bi clbi odir = toGhcDebugInfo NormalDebugInfo = toFlag True toGhcDebugInfo MaximalDebugInfo = toFlag True + hole_insts = map (\(k,(p,n)) -> (k, (InstalledPackageInfo.packageKey p,n))) + (instantiatedWith lbi) + -- | Strip out flags that are not supported in ghci filterGhciFlags :: [String] -> [String] filterGhciFlags = filter supported @@ -423,7 +430,7 @@ filterGhciFlags = filter supported supported _ = True mkGHCiLibName :: LibraryName -> String -mkGHCiLibName (LibraryName lib) = lib <.> "o" +mkGHCiLibName lib = getHSLibraryName lib <.> "o" ghcLookupProperty :: String -> Compiler -> Bool ghcLookupProperty prop comp = diff --git a/Cabal/Distribution/Simple/GHCJS.hs b/Cabal/Distribution/Simple/GHCJS.hs index 82784c45deab740799413ef649c6628c9c2e0c0f..2e5e90a7ef1cd1eb0b2c2365f2a429604677924d 100644 --- a/Cabal/Distribution/Simple/GHCJS.hs +++ b/Cabal/Distribution/Simple/GHCJS.hs @@ -26,11 +26,11 @@ import Distribution.InstalledPackageInfo ( InstalledPackageInfo ) import qualified Distribution.InstalledPackageInfo as InstalledPackageInfo ( InstalledPackageInfo_(..) ) +import Distribution.Package ( LibraryName(..), getHSLibraryName ) import Distribution.Simple.PackageIndex ( InstalledPackageIndex ) import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.Simple.LocalBuildInfo - ( LocalBuildInfo(..), ComponentLocalBuildInfo(..) - , LibraryName(..) ) + ( LocalBuildInfo(..), ComponentLocalBuildInfo(..) ) import qualified Distribution.Simple.Hpc as Hpc import Distribution.Simple.InstallDirs hiding ( absoluteInstallDirs ) import Distribution.Simple.BuildPaths @@ -301,11 +301,8 @@ buildOrReplLib :: Bool -> Verbosity -> Cabal.Flag (Maybe Int) -> PackageDescription -> LocalBuildInfo -> Library -> ComponentLocalBuildInfo -> IO () buildOrReplLib forRepl verbosity numJobs _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 libTargetDir = buildDir lbi + let libName@(LibraryName cname) = componentLibraryName clbi + libTargetDir = buildDir lbi whenVanillaLib forceVanilla = when (not forRepl && (forceVanilla || withVanillaLib lbi)) whenProfLib = when (not forRepl && withProfLib lbi) @@ -332,9 +329,6 @@ buildOrReplLib forRepl verbosity numJobs _pkg_descr lbi lib clbi = do -- Determine if program coverage should be enabled and if so, what -- '-hpcdir' should be. let isCoverageEnabled = fromFlag $ configCoverage $ configFlags lbi - -- Component name. Not 'libName' because that has the "HS" prefix - -- that GHC gives Haskell libraries. - cname = display $ PD.package $ localPkgDescr lbi distPref = fromFlag $ configDistPref $ configFlags lbi hpcdir way | isCoverageEnabled = toFlag $ Hpc.mixDir distPref way cname @@ -348,14 +342,13 @@ buildOrReplLib forRepl verbosity numJobs _pkg_descr lbi lib clbi = do baseOpts = componentGhcOptions verbosity lbi libBi clbi libTargetDir linkJsLibOpts = mempty { ghcOptExtra = toNubListR $ - [ "-link-js-lib" , (\(LibraryName l) -> l) libName + [ "-link-js-lib" , getHSLibraryName libName , "-js-lib-outputdir", libTargetDir ] ++ concatMap (\x -> ["-js-lib-src",x]) jsSrcs } vanillaOptsNoJsLib = baseOpts `mappend` mempty { ghcOptMode = toFlag GhcModeMake, ghcOptNumJobs = numJobs, - ghcOptPackageKey = toFlag (pkgKey lbi), ghcOptSigOf = hole_insts, ghcOptInputModules = toNubListR $ libModules lib, ghcOptHPCDir = hpcdir Hpc.Vanilla @@ -506,7 +499,6 @@ buildOrReplLib forRepl verbosity numJobs _pkg_descr lbi lib clbi = do ghcOptDynLinkMode = toFlag GhcDynamicOnly, ghcOptInputFiles = toNubListR dynamicObjectFiles, ghcOptOutputFile = toFlag sharedLibFilePath, - ghcOptPackageKey = toFlag (pkgKey lbi), ghcOptNoAutoLinkPackages = toFlag True, ghcOptPackageDBs = withPackageDB lbi, ghcOptPackages = toNubListR $ @@ -727,9 +719,9 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir _pkg lib clbi = do whenProf $ copyModuleFiles "js_p_hi" whenShared $ copyModuleFiles "js_dyn_hi" - whenVanilla $ mapM_ (installOrdinary builtDir targetDir . toJSLibName) vanillaLibNames - whenProf $ mapM_ (installOrdinary builtDir targetDir . toJSLibName) profileLibNames - whenShared $ mapM_ (installShared builtDir dynlibTargetDir . toJSLibName) sharedLibNames + whenVanilla $ installOrdinary builtDir targetDir $ toJSLibName vanillaLibName + whenProf $ installOrdinary builtDir targetDir $ toJSLibName profileLibName + whenShared $ installShared builtDir dynlibTargetDir $ toJSLibName sharedLibName when (ghcjsNativeToo $ compiler lbi) $ do -- copy .hi files over: @@ -738,10 +730,10 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir _pkg lib clbi = do whenShared $ copyModuleFiles "dyn_hi" -- copy the built library files over: - whenVanilla $ mapM_ (installOrdinary builtDir targetDir) vanillaLibNames - whenProf $ mapM_ (installOrdinary builtDir targetDir) profileLibNames - whenGHCi $ mapM_ (installOrdinary builtDir targetDir) ghciLibNames - whenShared $ mapM_ (installShared builtDir dynlibTargetDir) sharedLibNames + whenVanilla $ installOrdinary builtDir targetDir vanillaLibName + whenProf $ installOrdinary builtDir targetDir profileLibName + whenGHCi $ installOrdinary builtDir targetDir ghciLibName + whenShared $ installShared builtDir dynlibTargetDir sharedLibName where install isShared srcDir dstDir name = do @@ -762,11 +754,11 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir _pkg lib clbi = do >>= installOrdinaryFiles verbosity targetDir cid = compilerId (compiler lbi) - libNames = componentLibraries clbi - vanillaLibNames = map mkLibName libNames - profileLibNames = map mkProfLibName libNames - ghciLibNames = map Internal.mkGHCiLibName libNames - sharedLibNames = map (mkSharedLibName cid) libNames + libName = componentLibraryName clbi + vanillaLibName = mkLibName libName + profileLibName = mkProfLibName libName + ghciLibName = Internal.mkGHCiLibName libName + sharedLibName = (mkSharedLibName cid) libName hasLib = not $ null (libModules lib) && null (cSources (libBuildInfo lib)) @@ -810,7 +802,6 @@ libAbiHash verbosity _pkg_descr lbi lib clbi = do (componentGhcOptions verbosity lbi libBi clbi (buildDir lbi)) `mappend` mempty { ghcOptMode = toFlag GhcModeAbiHash, - ghcOptPackageKey = toFlag (pkgKey lbi), ghcOptInputModules = toNubListR $ exposedModules lib } profArgs = adjustExts "js_p_hi" "js_p_o" vanillaArgs `mappend` mempty { diff --git a/Cabal/Distribution/Simple/Haddock.hs b/Cabal/Distribution/Simple/Haddock.hs index 9e55b4352b420b69dd76120ab617cad5c2957498..473f26553984be211d472e61f4e2ba7487eaa5b9 100644 --- a/Cabal/Distribution/Simple/Haddock.hs +++ b/Cabal/Distribution/Simple/Haddock.hs @@ -27,7 +27,7 @@ import qualified Distribution.Simple.GHCJS as GHCJS import Distribution.Package ( PackageIdentifier(..) , Package(..) - , PackageName(..), packageName ) + , PackageName(..), packageName, LibraryName(..) ) import qualified Distribution.ModuleName as ModuleName import Distribution.PackageDescription as PD ( PackageDescription(..), BuildInfo(..), usedExtensions @@ -310,8 +310,7 @@ fromLibrary verbosity tmp lbi lib clbi htmlTemplate haddockVersion = do -- haddock to write them elsewhere. ghcOptObjDir = toFlag tmp, ghcOptHiDir = toFlag tmp, - ghcOptStubDir = toFlag tmp, - ghcOptPackageKey = toFlag $ pkgKey lbi + ghcOptStubDir = toFlag tmp } `mappend` getGhcCppOpts haddockVersion bi sharedOpts = vanillaOpts { ghcOptDynLinkMode = toFlag GhcDynamicOnly, @@ -619,7 +618,7 @@ haddockPackageFlags lbi clbi htmlTemplate = do haddockTemplateEnv :: LocalBuildInfo -> PackageIdentifier -> PathTemplateEnv haddockTemplateEnv lbi pkg_id = (PrefixVar, prefix (installDirTemplates lbi)) - : initialPathTemplateEnv pkg_id (pkgKey lbi) (compilerInfo (compiler lbi)) + : initialPathTemplateEnv pkg_id (LibraryName (display pkg_id)) (compilerInfo (compiler lbi)) (hostPlatform lbi) -- ------------------------------------------------------------------------------ diff --git a/Cabal/Distribution/Simple/InstallDirs.hs b/Cabal/Distribution/Simple/InstallDirs.hs index 312622d035618ab5b7e5b98ff06b3d1e9093a94b..ac911237d662b4ea465158113ec26581fb5da538 100644 --- a/Cabal/Distribution/Simple/InstallDirs.hs +++ b/Cabal/Distribution/Simple/InstallDirs.hs @@ -57,7 +57,7 @@ import System.FilePath ((</>), isPathSeparator, pathSeparator) import System.FilePath (dropDrive) import Distribution.Package - ( PackageIdentifier, PackageKey, packageName, packageVersion, packageKeyLibraryName ) + ( PackageIdentifier, packageName, packageVersion, LibraryName ) import Distribution.System ( OS(..), buildOS, Platform(..) ) import Distribution.Compiler @@ -287,13 +287,13 @@ substituteInstallDirTemplates env dirs = dirs' -- substituting for all the variables in the abstract paths, to get real -- absolute path. absoluteInstallDirs :: PackageIdentifier - -> PackageKey + -> LibraryName -> CompilerInfo -> CopyDest -> Platform -> InstallDirs PathTemplate -> InstallDirs FilePath -absoluteInstallDirs pkgId pkg_key compilerId copydest platform dirs = +absoluteInstallDirs pkgId libname compilerId copydest platform dirs = (case copydest of CopyTo destdir -> fmap ((destdir </>) . dropDrive) _ -> id) @@ -301,7 +301,7 @@ absoluteInstallDirs pkgId pkg_key compilerId copydest platform dirs = . fmap fromPathTemplate $ substituteInstallDirTemplates env dirs where - env = initialPathTemplateEnv pkgId pkg_key compilerId platform + env = initialPathTemplateEnv pkgId libname compilerId platform -- |The location prefix for the /copy/ command. @@ -317,12 +317,12 @@ data CopyDest -- independent\" package). -- prefixRelativeInstallDirs :: PackageIdentifier - -> PackageKey + -> LibraryName -> CompilerInfo -> Platform -> InstallDirTemplates -> InstallDirs (Maybe FilePath) -prefixRelativeInstallDirs pkgId pkg_key compilerId platform dirs = +prefixRelativeInstallDirs pkgId libname compilerId platform dirs = fmap relative . appendSubdirs combinePathTemplate $ -- substitute the path template into each other, except that we map @@ -332,7 +332,7 @@ prefixRelativeInstallDirs pkgId pkg_key compilerId platform dirs = prefix = PathTemplate [Variable PrefixVar] } where - env = initialPathTemplateEnv pkgId pkg_key compilerId platform + env = initialPathTemplateEnv pkgId libname compilerId platform -- If it starts with $prefix then it's relative and produce the relative -- path by stripping off $prefix/ or $prefix @@ -372,7 +372,6 @@ data PathTemplateVariable = | PkgNameVar -- ^ The @$pkg@ package name path variable | PkgVerVar -- ^ The @$version@ package version path variable | PkgIdVar -- ^ The @$pkgid@ package Id path variable, eg @foo-1.0@ - | PkgKeyVar -- ^ The @$pkgkey@ package key path variable | LibNameVar -- ^ The @$libname@ expanded package key path variable | CompilerVar -- ^ The compiler name and version, eg @ghc-6.6.1@ | OSVar -- ^ The operating system name, eg @windows@ or @linux@ @@ -416,22 +415,21 @@ substPathTemplate environment (PathTemplate template) = -- | The initial environment has all the static stuff but no paths initialPathTemplateEnv :: PackageIdentifier - -> PackageKey + -> LibraryName -> CompilerInfo -> Platform -> PathTemplateEnv -initialPathTemplateEnv pkgId pkg_key compiler platform = - packageTemplateEnv pkgId pkg_key +initialPathTemplateEnv pkgId libname compiler platform = + packageTemplateEnv pkgId libname ++ compilerTemplateEnv compiler ++ platformTemplateEnv platform ++ abiTemplateEnv compiler platform -packageTemplateEnv :: PackageIdentifier -> PackageKey -> PathTemplateEnv -packageTemplateEnv pkgId pkg_key = +packageTemplateEnv :: PackageIdentifier -> LibraryName -> PathTemplateEnv +packageTemplateEnv pkgId libname = [(PkgNameVar, PathTemplate [Ordinary $ display (packageName pkgId)]) ,(PkgVerVar, PathTemplate [Ordinary $ display (packageVersion pkgId)]) - ,(PkgKeyVar, PathTemplate [Ordinary $ display pkg_key]) - ,(LibNameVar, PathTemplate [Ordinary $ packageKeyLibraryName pkgId pkg_key]) + ,(LibNameVar, PathTemplate [Ordinary $ display libname]) ,(PkgIdVar, PathTemplate [Ordinary $ display pkgId]) ] @@ -480,7 +478,6 @@ installDirsTemplateEnv dirs = instance Show PathTemplateVariable where show PrefixVar = "prefix" - show PkgKeyVar = "pkgkey" show LibNameVar = "libname" show BindirVar = "bindir" show LibdirVar = "libdir" @@ -518,7 +515,7 @@ instance Read PathTemplateVariable where ,("docdir", DocdirVar) ,("htmldir", HtmldirVar) ,("pkgid", PkgIdVar) - ,("pkgkey", PkgKeyVar) + ,("pkgkey", LibNameVar) -- backwards compatibility ,("libname", LibNameVar) ,("pkg", PkgNameVar) ,("version", PkgVerVar) diff --git a/Cabal/Distribution/Simple/LHC.hs b/Cabal/Distribution/Simple/LHC.hs index 2c63a67ee14fa15f92aa8c047fbb96ad43b94d3a..bd2cc59f18aaa7f3cd42a91e71b615743ab548da 100644 --- a/Cabal/Distribution/Simple/LHC.hs +++ b/Cabal/Distribution/Simple/LHC.hs @@ -54,13 +54,12 @@ import Distribution.Simple.PackageIndex import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.ParseUtils ( ParseResult(..) ) import Distribution.Simple.LocalBuildInfo - ( LocalBuildInfo(..), ComponentLocalBuildInfo(..), - LibraryName(..) ) + ( LocalBuildInfo(..), ComponentLocalBuildInfo(..) ) import Distribution.Simple.InstallDirs import Distribution.Simple.BuildPaths import Distribution.Simple.Utils import Distribution.Package - ( Package(..) ) + ( Package(..), LibraryName, getHSLibraryName ) import qualified Distribution.ModuleName as ModuleName import Distribution.Simple.Program ( Program(..), ConfiguredProgram(..), ProgramConfiguration @@ -319,12 +318,8 @@ 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 + let libName = componentLibraryName clbi + pref = buildDir lbi pkgid = packageId pkg_descr runGhcProg = rawSystemProgramConf verbosity lhcProgram (withPrograms lbi) ifVanillaLib forceVanilla = when (forceVanilla || withVanillaLib lbi) @@ -688,7 +683,7 @@ ghcCcOptions lbi bi clbi odir ++ ["-odir", odir] mkGHCiLibName :: LibraryName -> String -mkGHCiLibName (LibraryName lib) = lib <.> "o" +mkGHCiLibName lib = getHSLibraryName lib <.> "o" -- ----------------------------------------------------------------------------- -- Installing @@ -755,18 +750,18 @@ installLib verbosity lbi targetDir dynlibTargetDir builtDir _pkg lib clbi = do flip mapM_ hcrFiles $ \(srcBase, srcFile) -> runLhc ["--install-library", srcBase </> srcFile] -- copy the built library files over: - ifVanilla $ mapM_ (copy builtDir targetDir) vanillaLibNames - ifProf $ mapM_ (copy builtDir targetDir) profileLibNames - ifGHCi $ mapM_ (copy builtDir targetDir) ghciLibNames - ifShared $ mapM_ (copy builtDir dynlibTargetDir) sharedLibNames + ifVanilla $ copy builtDir targetDir vanillaLibName + ifProf $ copy builtDir targetDir profileLibName + ifGHCi $ copy builtDir targetDir ghciLibName + ifShared $ copy builtDir dynlibTargetDir sharedLibName where cid = compilerId (compiler lbi) - libNames = componentLibraries clbi - vanillaLibNames = map mkLibName libNames - profileLibNames = map mkProfLibName libNames - ghciLibNames = map mkGHCiLibName libNames - sharedLibNames = map (mkSharedLibName cid) libNames + libName = componentLibraryName clbi + vanillaLibName = mkLibName libName + profileLibName = mkProfLibName libName + ghciLibName = mkGHCiLibName libName + sharedLibName = mkSharedLibName cid libName hasLib = not $ null (libModules lib) && null (cSources (libBuildInfo lib)) diff --git a/Cabal/Distribution/Simple/LocalBuildInfo.hs b/Cabal/Distribution/Simple/LocalBuildInfo.hs index 76cb64c97b548d78867467d8d552bbecfbf548b9..96043ba8adee1d0594707352d40c796a608e9f58 100644 --- a/Cabal/Distribution/Simple/LocalBuildInfo.hs +++ b/Cabal/Distribution/Simple/LocalBuildInfo.hs @@ -21,13 +21,14 @@ module Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..), externalPackageDeps, inplacePackageId, + localPackageKey, + localLibraryName, -- * Buildable package components Component(..), ComponentName(..), showComponentName, ComponentLocalBuildInfo(..), - LibraryName(..), foldComponent, componentName, componentBuildInfo, @@ -70,8 +71,8 @@ import Distribution.PackageDescription , BuildInfo(buildable), Benchmark(..), ModuleRenaming(..) ) import qualified Distribution.InstalledPackageInfo as Installed import Distribution.Package - ( PackageId, Package(..), InstalledPackageId(..), PackageKey - , PackageName ) + ( PackageId, Package(..), InstalledPackageId(..) + , PackageName, LibraryName(..), PackageKey(..) ) import Distribution.Simple.Compiler ( Compiler, compilerInfo, PackageDBStack, DebugInfoLevel , OptimisationLevel, ProfDetailLevel ) @@ -128,9 +129,6 @@ data LocalBuildInfo = LocalBuildInfo { localPkgDescr :: PackageDescription, -- ^ The resolved package description, that does not contain -- any conditionals. - pkgKey :: PackageKey, - -- ^ The package key for the current build, calculated from - -- the package ID and the dependency graph. instantiatedWith :: [(ModuleName, (InstalledPackageInfo, ModuleName))], withPrograms :: ProgramConfiguration, -- ^Location and args for all programs withPackageDB :: PackageDBStack, -- ^What package database to use, global\/user @@ -154,6 +152,26 @@ data LocalBuildInfo = LocalBuildInfo { instance Binary LocalBuildInfo +-- | Extract the 'PackageKey' from the library component of a +-- 'LocalBuildInfo' if it exists, or make a fake package key based +-- on the package ID. +localPackageKey :: LocalBuildInfo -> PackageKey +localPackageKey lbi = + foldr go (OldPackageKey (package (localPkgDescr lbi))) (componentsConfigs lbi) + where go (_, clbi, _) old_pk = case clbi of + LibComponentLocalBuildInfo { componentPackageKey = pk } -> pk + _ -> old_pk + +-- | Extract the 'LibraryName' from the library component of a +-- 'LocalBuildInfo' if it exists, or make a library name based +-- on the package ID. +localLibraryName :: LocalBuildInfo -> LibraryName +localLibraryName lbi = + foldr go (LibraryName (display (package (localPkgDescr lbi)))) (componentsConfigs lbi) + where go (_, clbi, _) old_n = case clbi of + LibComponentLocalBuildInfo { componentLibraryName = n } -> n + _ -> old_n + -- | External package dependencies for the package as a whole. This is the -- union of the individual 'componentPackageDeps', less any internal deps. externalPackageDeps :: LocalBuildInfo -> [(InstalledPackageId, PackageId)] @@ -204,9 +222,10 @@ data ComponentLocalBuildInfo -- 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)], + componentPackageKey :: PackageKey, + componentLibraryName :: LibraryName, componentExposedModules :: [Installed.ExposedModule], - componentPackageRenaming :: Map PackageName ModuleRenaming, - componentLibraries :: [LibraryName] + componentPackageRenaming :: Map PackageName ModuleRenaming } | ExeComponentLocalBuildInfo { componentPackageDeps :: [(InstalledPackageId, PackageId)], @@ -235,11 +254,6 @@ foldComponent _ f _ _ (CExe exe) = f exe foldComponent _ _ f _ (CTest tst) = f tst foldComponent _ _ _ f (CBench bch) = f bch -data LibraryName = LibraryName String - deriving (Generic, Read, Show) - -instance Binary LibraryName - componentBuildInfo :: Component -> BuildInfo componentBuildInfo = foldComponent libBuildInfo buildInfo testBuildInfo benchmarkBuildInfo @@ -478,7 +492,7 @@ absoluteInstallDirs :: PackageDescription -> LocalBuildInfo -> CopyDest absoluteInstallDirs pkg lbi copydest = InstallDirs.absoluteInstallDirs (packageId pkg) - (pkgKey lbi) + (localLibraryName lbi) (compilerInfo (compiler lbi)) copydest (hostPlatform lbi) @@ -490,7 +504,7 @@ prefixRelativeInstallDirs :: PackageId -> LocalBuildInfo prefixRelativeInstallDirs pkg_descr lbi = InstallDirs.prefixRelativeInstallDirs (packageId pkg_descr) - (pkgKey lbi) + (localLibraryName lbi) (compilerInfo (compiler lbi)) (hostPlatform lbi) (installDirTemplates lbi) @@ -501,6 +515,6 @@ substPathTemplate pkgid lbi = fromPathTemplate . ( InstallDirs.substPathTemplate env ) where env = initialPathTemplateEnv pkgid - (pkgKey lbi) + (localLibraryName lbi) (compilerInfo (compiler lbi)) (hostPlatform lbi) diff --git a/Cabal/Distribution/Simple/Register.hs b/Cabal/Distribution/Simple/Register.hs index c39d4043c2499b2e75e8333539cd45d2a16ac2e4..4d20c872c837fe8b1f4c40e35484b422351dab14 100644 --- a/Cabal/Distribution/Simple/Register.hs +++ b/Cabal/Distribution/Simple/Register.hs @@ -39,7 +39,6 @@ module Distribution.Simple.Register ( import Distribution.Simple.LocalBuildInfo ( LocalBuildInfo(..), ComponentLocalBuildInfo(..) , ComponentName(..), getComponentLocalBuildInfo - , LibraryName(..) , InstallDirs(..), absoluteInstallDirs ) import Distribution.Simple.BuildPaths (haddockName) @@ -65,7 +64,8 @@ import Distribution.Simple.Setup import Distribution.PackageDescription ( PackageDescription(..), Library(..), BuildInfo(..), libModules ) import Distribution.Package - ( Package(..), packageName, InstalledPackageId(..) ) + ( Package(..), packageName, InstalledPackageId(..) + , getHSLibraryName ) import Distribution.InstalledPackageInfo ( InstalledPackageInfo, InstalledPackageInfo_(InstalledPackageInfo) , showInstalledPackageInfo ) @@ -299,7 +299,7 @@ generalInstalledPackageInfo adjustRelIncDirs pkg ipid lib lbi clbi installDirs = InstalledPackageInfo { IPI.installedPackageId = ipid, IPI.sourcePackageId = packageId pkg, - IPI.packageKey = pkgKey lbi, + IPI.packageKey = componentPackageKey clbi, IPI.license = license pkg, IPI.copyright = copyright pkg, IPI.maintainer = maintainer pkg, @@ -324,9 +324,9 @@ generalInstalledPackageInfo adjustRelIncDirs pkg ipid lib lbi clbi installDirs = then libdir installDirs : extraLibDirs bi else extraLibDirs bi, IPI.dataDir = datadir installDirs, - IPI.hsLibraries = [ libname - | LibraryName libname <- componentLibraries clbi - , hasLibrary ], + IPI.hsLibraries = if hasLibrary + then [getHSLibraryName (componentLibraryName clbi)] + else [], IPI.extraLibraries = extraLibs bi, IPI.extraGHCiLibraries = extraGHCiLibs bi, IPI.includeDirs = absinc ++ adjustRelIncDirs relinc, diff --git a/Cabal/Distribution/Simple/Test.hs b/Cabal/Distribution/Simple/Test.hs index 4c3bfc15cd4033f41242bcbd21ad44051afa5062..25fdab5dcf2d68afe7e0efb0a94c68393988dd24 100644 --- a/Cabal/Distribution/Simple/Test.hs +++ b/Cabal/Distribution/Simple/Test.hs @@ -25,7 +25,7 @@ import Distribution.Simple.InstallDirs ( fromPathTemplate, initialPathTemplateEnv, substPathTemplate , PathTemplate ) import qualified Distribution.Simple.LocalBuildInfo as LBI - ( LocalBuildInfo(..) ) + ( LocalBuildInfo(..), localLibraryName ) import Distribution.Simple.Setup ( TestFlags(..), fromFlag, configCoverage ) import Distribution.Simple.UserHooks ( Args ) import qualified Distribution.Simple.Test.ExeV10 as ExeV10 @@ -132,5 +132,5 @@ packageLogPath template pkg_descr lbi = fromPathTemplate $ substPathTemplate env template where env = initialPathTemplateEnv - (PD.package pkg_descr) (LBI.pkgKey lbi) + (PD.package pkg_descr) (LBI.localLibraryName lbi) (compilerInfo $ LBI.compiler lbi) (LBI.hostPlatform lbi) diff --git a/Cabal/Distribution/Simple/Test/ExeV10.hs b/Cabal/Distribution/Simple/Test/ExeV10.hs index 6dc622ede668a10710c70764ecf975853e92bdd4..04fca1ed9b144a195b3caef128a75925ae567264 100644 --- a/Cabal/Distribution/Simple/Test/ExeV10.hs +++ b/Cabal/Distribution/Simple/Test/ExeV10.hs @@ -163,6 +163,6 @@ testOption pkg_descr lbi suite template = fromPathTemplate $ substPathTemplate env template where env = initialPathTemplateEnv - (PD.package pkg_descr) (LBI.pkgKey lbi) + (PD.package pkg_descr) (LBI.localLibraryName lbi) (compilerInfo $ LBI.compiler lbi) (LBI.hostPlatform lbi) ++ [(TestSuiteNameVar, toPathTemplate $ PD.testName suite)] diff --git a/Cabal/Distribution/Simple/Test/LibV09.hs b/Cabal/Distribution/Simple/Test/LibV09.hs index 86447474c40c98e4c10ae32f97055215f6593c81..482953822d3a5765ff205c8a63d17a5e5ed5fd74 100644 --- a/Cabal/Distribution/Simple/Test/LibV09.hs +++ b/Cabal/Distribution/Simple/Test/LibV09.hs @@ -167,7 +167,7 @@ testOption pkg_descr lbi suite template = fromPathTemplate $ substPathTemplate env template where env = initialPathTemplateEnv - (PD.package pkg_descr) (LBI.pkgKey lbi) + (PD.package pkg_descr) (LBI.localLibraryName lbi) (compilerInfo $ LBI.compiler lbi) (LBI.hostPlatform lbi) ++ [(TestSuiteNameVar, toPathTemplate $ PD.testName suite)] diff --git a/Cabal/Distribution/Simple/Test/Log.hs b/Cabal/Distribution/Simple/Test/Log.hs index 4cd95a9633d2ea4d56e1f17bd298c149a6d2b7e7..98de12ca2e76455a433d93119479badd0d169efc 100644 --- a/Cabal/Distribution/Simple/Test/Log.hs +++ b/Cabal/Distribution/Simple/Test/Log.hs @@ -113,7 +113,7 @@ testSuiteLogPath template pkg_descr lbi name result = fromPathTemplate $ substPathTemplate env template where env = initialPathTemplateEnv - (PD.package pkg_descr) (LBI.pkgKey lbi) + (PD.package pkg_descr) (LBI.localLibraryName lbi) (compilerInfo $ LBI.compiler lbi) (LBI.hostPlatform lbi) ++ [ (TestSuiteNameVar, toPathTemplate name) , (TestSuiteResultVar, toPathTemplate $ resultString result) diff --git a/Cabal/tests/PackageTests/DeterministicAr/Check.hs b/Cabal/tests/PackageTests/DeterministicAr/Check.hs index 891aa350ae3dcb06e06dcfbc60de91bc410e0d27..27bd986f0d116a7996b7d3dc54f4bb8f4bfdd2ad 100644 --- a/Cabal/tests/PackageTests/DeterministicAr/Check.hs +++ b/Cabal/tests/PackageTests/DeterministicAr/Check.hs @@ -18,11 +18,11 @@ import System.IO import Test.Tasty.HUnit (Assertion, assertFailure) import Distribution.Compiler (CompilerFlavor(..), CompilerId(..)) -import Distribution.Package (packageKeyHash) +import Distribution.Package (getHSLibraryName) import Distribution.Version (Version(..)) import Distribution.Simple.Compiler (compilerId) import Distribution.Simple.Configure (getPersistBuildConfig) -import Distribution.Simple.LocalBuildInfo (LocalBuildInfo, compiler, pkgKey) +import Distribution.Simple.LocalBuildInfo (LocalBuildInfo, compiler, localLibraryName) -- Perhaps these should live in PackageTester. @@ -82,11 +82,9 @@ checkMetadata :: LocalBuildInfo -> FilePath -> Assertion checkMetadata lbi dir = withBinaryFile path ReadMode $ \ h -> do hFileSize h >>= checkArchive h where - path = dir </> "libHS" ++ this ++ "-0" - ++ (if ghc_7_10 then ("-" ++ packageKeyHash (pkgKey lbi)) else "") - ++ ".a" + path = dir </> "lib" ++ getHSLibraryName (localLibraryName lbi) ++ ".a" - ghc_7_10 = case compilerId (compiler lbi) of + _ghc_7_10 = case compilerId (compiler lbi) of CompilerId GHC version | version >= Version [7, 10] [] -> True _ -> False diff --git a/Cabal/tests/PackageTests/TestSuiteExeV10/Check.hs b/Cabal/tests/PackageTests/TestSuiteExeV10/Check.hs index a8e53e060fde18c60be7563b9e9c7eaea8182702..5ea4610a030ee85c24131830a12ce1bcd642c80f 100644 --- a/Cabal/tests/PackageTests/TestSuiteExeV10/Check.hs +++ b/Cabal/tests/PackageTests/TestSuiteExeV10/Check.hs @@ -12,7 +12,7 @@ import Distribution.Compiler (CompilerFlavor(..), CompilerId(..)) import Distribution.PackageDescription (package) import Distribution.Simple.Compiler (compilerId) import Distribution.Simple.Configure (getPersistBuildConfig) -import Distribution.Simple.LocalBuildInfo (compiler, localPkgDescr, pkgKey) +import Distribution.Simple.LocalBuildInfo (compiler, localPkgDescr, localPackageKey) import Distribution.Simple.Hpc import Distribution.Simple.Program.Builtin (hpcProgram) import Distribution.Simple.Program.Db @@ -80,7 +80,7 @@ checkTestWithHpc config name extraOpts = do CompilerId comp version = compilerId (compiler lbi) subdir | comp == GHC && version >= Version [7, 10] [] = - display (pkgKey lbi) + display (localPackageKey lbi) | otherwise = display (package $ localPkgDescr lbi) mapM_ shouldExist [ mixDir distPref' way "my-0.1" </> subdir </> "Foo.mix" diff --git a/cabal-install/Distribution/Client/Install.hs b/cabal-install/Distribution/Client/Install.hs index c8cef42e59829324162cd3fff95f5f28bae0822a..90f057b30ad5ea4b152a3f5b947a1c39fbb77a59 100644 --- a/cabal-install/Distribution/Client/Install.hs +++ b/cabal-install/Distribution/Client/Install.hs @@ -137,7 +137,7 @@ import Distribution.Simple.InstallDirs as InstallDirs , initialPathTemplateEnv, installDirsTemplateEnv ) import Distribution.Package ( PackageIdentifier(..), PackageId, packageName, packageVersion - , Package(..), PackageKey + , Package(..), LibraryName , Dependency(..), thisPackageVersion, InstalledPackageId, installedPackageId ) import qualified Distribution.PackageDescription as PackageDescription import Distribution.PackageDescription @@ -716,7 +716,7 @@ reportPlanningFailure verbosity case logFile of Nothing -> return () Just template -> forM_ pkgids $ \pkgid -> - let env = initialPathTemplateEnv pkgid dummyPackageKey + let env = initialPathTemplateEnv pkgid dummyLibraryName (compilerInfo comp) platform path = fromPathTemplate $ substPathTemplate env template in writeFile path message @@ -725,10 +725,10 @@ reportPlanningFailure verbosity reportFailure = fromFlag (installReportPlanningFailure installFlags) logFile = flagToMaybe (installLogFile installFlags) - -- A PackageKey is calculated from the transitive closure of + -- A LibraryName is calculated from the transitive closure of -- dependencies, but when the solver fails we don't have that. -- So we fail. - dummyPackageKey = error "reportPlanningFailure: package key not available" + dummyLibraryName = error "reportPlanningFailure: library name not available" -- | If a 'PackageSpecifier' refers to a single package, return Just that package. theSpecifiedPackage :: Package pkg => PackageSpecifier pkg -> Maybe PackageId @@ -993,7 +993,7 @@ data InstallMisc = InstallMisc { -- | If logging is enabled, contains location of the log file and the verbosity -- level for logging. -type UseLogFile = Maybe (PackageIdentifier -> PackageKey -> FilePath, Verbosity) +type UseLogFile = Maybe (PackageIdentifier -> LibraryName -> FilePath, Verbosity) performInstallations :: Verbosity -> InstallArgs @@ -1022,13 +1022,13 @@ performInstallations verbosity executeInstallPlan verbosity comp jobControl useLogFile installPlan $ \rpkg -> -- Calculate the package key (ToDo: Is this right for source install) - let pkg_key = readyPackageKey comp rpkg in + let libname = readyLibraryName comp rpkg in installReadyPackage platform cinfo configFlags rpkg $ \configFlags' src pkg pkgoverride -> fetchSourcePackage transport verbosity fetchLimit src $ \src' -> installLocalPackage verbosity buildLimit (packageId pkg) src' distPref $ \mpath -> - installUnpackedPackage verbosity buildLimit installLock numJobs pkg_key + installUnpackedPackage verbosity buildLimit installLock numJobs libname (setupScriptOptions installedPkgIndex cacheLock rpkg) miscOptions configFlags' installFlags haddockFlags cinfo platform pkg pkgoverride mpath useLogFile @@ -1096,11 +1096,11 @@ performInstallations verbosity | parallelInstall = False | otherwise = False - substLogFileName :: PathTemplate -> PackageIdentifier -> PackageKey -> FilePath - substLogFileName template pkg pkg_key = fromPathTemplate + substLogFileName :: PathTemplate -> PackageIdentifier -> LibraryName -> FilePath + substLogFileName template pkg libname = fromPathTemplate . substPathTemplate env $ template - where env = initialPathTemplateEnv (packageId pkg) pkg_key + where env = initialPathTemplateEnv (packageId pkg) libname (compilerInfo comp) platform miscOptions = InstallMisc { @@ -1115,7 +1115,7 @@ performInstallations verbosity executeInstallPlan :: Verbosity -> Compiler - -> JobControl IO (PackageId, PackageKey, BuildResult) + -> JobControl IO (PackageId, LibraryName, BuildResult) -> UseLogFile -> InstallPlan -> (ReadyPackage -> IO BuildResult) @@ -1132,10 +1132,10 @@ executeInstallPlan verbosity comp jobCtl useLogFile plan0 installPkg = [ do info verbosity $ "Ready to install " ++ display pkgid spawnJob jobCtl $ do buildResult <- installPkg pkg - return (packageId pkg, pkg_key, buildResult) + return (packageId pkg, libname, buildResult) | pkg <- pkgs , let pkgid = packageId pkg - pkg_key = readyPackageKey comp pkg ] + libname = readyLibraryName comp pkg ] let taskCount' = taskCount + length pkgs plan' = InstallPlan.processing pkgs plan @@ -1143,8 +1143,8 @@ executeInstallPlan verbosity comp jobCtl useLogFile plan0 installPkg = waitForTasks taskCount plan = do info verbosity $ "Waiting for install task to finish..." - (pkgid, pkg_key, buildResult) <- collectJob jobCtl - printBuildResult pkgid pkg_key buildResult + (pkgid, libname, buildResult) <- collectJob jobCtl + printBuildResult pkgid libname buildResult let taskCount' = taskCount-1 plan' = updatePlan pkgid buildResult plan tryNewTasks taskCount' plan' @@ -1164,8 +1164,8 @@ executeInstallPlan verbosity comp jobCtl useLogFile plan0 installPkg = -- Print build log if something went wrong, and 'Installed $PKGID' -- otherwise. - printBuildResult :: PackageId -> PackageKey -> BuildResult -> IO () - printBuildResult pkgid pkg_key buildResult = case buildResult of + printBuildResult :: PackageId -> LibraryName -> BuildResult -> IO () + printBuildResult pkgid libname buildResult = case buildResult of (Right _) -> notice verbosity $ "Installed " ++ display pkgid (Left _) -> do notice verbosity $ "Failed to install " ++ display pkgid @@ -1173,7 +1173,7 @@ executeInstallPlan verbosity comp jobCtl useLogFile plan0 installPkg = case useLogFile of Nothing -> return () Just (mkLogFileName, _) -> do - let logName = mkLogFileName pkgid pkg_key + let logName = mkLogFileName pkgid libname putStr $ "Build log ( " ++ logName ++ " ):\n" printFile logName @@ -1322,7 +1322,7 @@ installUnpackedPackage -> JobLimit -> Lock -> Int - -> PackageKey + -> LibraryName -> SetupScriptOptions -> InstallMisc -> ConfigFlags @@ -1335,7 +1335,7 @@ installUnpackedPackage -> Maybe FilePath -- ^ Directory to change to before starting the installation. -> UseLogFile -- ^ File to log output to (if any) -> IO BuildResult -installUnpackedPackage verbosity buildLimit installLock numJobs pkg_key +installUnpackedPackage verbosity buildLimit installLock numJobs libname scriptOptions miscOptions configFlags installFlags haddockFlags cinfo platform pkg pkgoverride workingDir useLogFile = do @@ -1397,7 +1397,7 @@ installUnpackedPackage verbosity buildLimit installLock numJobs pkg_key maybePkgConf <- maybeGenPkgConf mLogPath -- Actual installation - withWin32SelfUpgrade verbosity pkg_key configFlags cinfo platform pkg $ do + withWin32SelfUpgrade verbosity libname configFlags cinfo platform pkg $ do case rootCmd miscOptions of (Just cmd) -> reexec cmd Nothing -> do @@ -1447,7 +1447,7 @@ installUnpackedPackage verbosity buildLimit installLock numJobs pkg_key } where CompilerId flavor _ = compilerInfoId cinfo - env = initialPathTemplateEnv pkgid pkg_key cinfo platform + env = initialPathTemplateEnv pkgid libname cinfo platform userInstall = fromFlagOrDefault defaultUserInstall (configUserInstall configFlags') @@ -1481,7 +1481,7 @@ installUnpackedPackage verbosity buildLimit installLock numJobs pkg_key case useLogFile of Nothing -> return Nothing Just (mkLogFileName, _) -> do - let logFileName = mkLogFileName (packageId pkg) pkg_key + let logFileName = mkLogFileName (packageId pkg) libname logDir = takeDirectory logFileName unless (null logDir) $ createDirectoryIfMissing True logDir logFileExists <- doesFileExist logFileName @@ -1529,14 +1529,14 @@ onFailure result action = -- ------------------------------------------------------------ withWin32SelfUpgrade :: Verbosity - -> PackageKey + -> LibraryName -> ConfigFlags -> CompilerInfo -> Platform -> PackageDescription -> IO a -> IO a withWin32SelfUpgrade _ _ _ _ _ _ action | buildOS /= Windows = action -withWin32SelfUpgrade verbosity pkg_key configFlags cinfo platform pkg action = do +withWin32SelfUpgrade verbosity libname configFlags cinfo platform pkg action = do defaultDirs <- InstallDirs.defaultInstallDirs compFlavor @@ -1564,9 +1564,9 @@ withWin32SelfUpgrade verbosity pkg_key configFlags cinfo platform pkg action = d templateDirs = InstallDirs.combineInstallDirs fromFlagOrDefault defaultDirs (configInstallDirs configFlags) absoluteDirs = InstallDirs.absoluteInstallDirs - pkgid pkg_key + pkgid libname cinfo InstallDirs.NoCopyDest platform templateDirs substTemplate = InstallDirs.fromPathTemplate . InstallDirs.substPathTemplate env - where env = InstallDirs.initialPathTemplateEnv pkgid pkg_key cinfo platform + where env = InstallDirs.initialPathTemplateEnv pkgid libname cinfo platform diff --git a/cabal-install/Distribution/Client/InstallSymlink.hs b/cabal-install/Distribution/Client/InstallSymlink.hs index 0ea1921688de2a85164c54fa91c791bf8340beeb..6a171986ea786bd3cc8a90eb9fca44cd5b4433c4 100644 --- a/cabal-install/Distribution/Client/InstallSymlink.hs +++ b/cabal-install/Distribution/Client/InstallSymlink.hs @@ -44,7 +44,8 @@ import qualified Distribution.Client.InstallPlan as InstallPlan import Distribution.Client.InstallPlan (InstallPlan) import Distribution.Package - ( PackageIdentifier, Package(packageId), mkPackageKey, PackageKey ) + ( PackageIdentifier, Package(packageId), mkPackageKey + , packageKeyLibraryName, LibraryName ) import Distribution.Compiler ( CompilerId(..) ) import qualified Distribution.PackageDescription as PackageDescription @@ -112,7 +113,7 @@ symlinkBinaries comp configFlags installFlags plan = -- TODO: do we want to do this here? : -- createDirectoryIfMissing True publicBinDir fmap catMaybes $ sequence - [ do privateBinDir <- pkgBinDir pkg pkg_key + [ do privateBinDir <- pkgBinDir pkg libname ok <- symlinkBinary publicBinDir privateBinDir publicExeName privateExeName @@ -123,11 +124,12 @@ symlinkBinaries comp configFlags installFlags plan = | (ReadyPackage _ _flags _ deps, pkg, exe) <- exes , let pkgid = packageId pkg pkg_key = mkPackageKey (packageKeySupported comp) pkgid - (map Installed.packageKey (CD.nonSetupDeps deps)) [] + (map Installed.libraryName (CD.nonSetupDeps deps)) + libname = packageKeyLibraryName pkgid pkg_key publicExeName = PackageDescription.exeName exe privateExeName = prefix ++ publicExeName ++ suffix - prefix = substTemplate pkgid pkg_key prefixTemplate - suffix = substTemplate pkgid pkg_key suffixTemplate ] + prefix = substTemplate pkgid libname prefixTemplate + suffix = substTemplate pkgid libname suffixTemplate ] where exes = [ (cpkg, pkg, exe) @@ -146,8 +148,8 @@ symlinkBinaries comp configFlags installFlags plan = -- This is sadly rather complicated. We're kind of re-doing part of the -- configuration for the package. :-( - pkgBinDir :: PackageDescription -> PackageKey -> IO FilePath - pkgBinDir pkg pkg_key = do + pkgBinDir :: PackageDescription -> LibraryName -> IO FilePath + pkgBinDir pkg libname = do defaultDirs <- InstallDirs.defaultInstallDirs compilerFlavor (fromFlag (configUserInstall configFlags)) @@ -155,14 +157,14 @@ symlinkBinaries comp configFlags installFlags plan = let templateDirs = InstallDirs.combineInstallDirs fromFlagOrDefault defaultDirs (configInstallDirs configFlags) absoluteDirs = InstallDirs.absoluteInstallDirs - (packageId pkg) pkg_key + (packageId pkg) libname cinfo InstallDirs.NoCopyDest platform templateDirs canonicalizePath (InstallDirs.bindir absoluteDirs) - substTemplate pkgid pkg_key = InstallDirs.fromPathTemplate + substTemplate pkgid libname = InstallDirs.fromPathTemplate . InstallDirs.substPathTemplate env - where env = InstallDirs.initialPathTemplateEnv pkgid pkg_key + where env = InstallDirs.initialPathTemplateEnv pkgid libname cinfo platform fromFlagTemplate = fromFlagOrDefault (InstallDirs.toPathTemplate "") diff --git a/cabal-install/Distribution/Client/Types.hs b/cabal-install/Distribution/Client/Types.hs index 1ac90a1324158b8456d79205ae7e97fd1f3fd588..129f65b489d7cca51249169b2e075f93ada8b122 100644 --- a/cabal-install/Distribution/Client/Types.hs +++ b/cabal-install/Distribution/Client/Types.hs @@ -17,7 +17,8 @@ module Distribution.Client.Types where import Distribution.Package ( PackageName, PackageId, Package(..) , mkPackageKey, PackageKey, InstalledPackageId(..) - , HasInstalledPackageId(..), PackageInstalled(..) ) + , HasInstalledPackageId(..), PackageInstalled(..) + , LibraryName, packageKeyLibraryName ) import Distribution.InstalledPackageInfo ( InstalledPackageInfo ) import Distribution.PackageDescription @@ -154,7 +155,13 @@ instance HasInstalledPackageId ReadyPackage where readyPackageKey :: Compiler -> ReadyPackage -> PackageKey readyPackageKey comp (ReadyPackage pkg _ _ deps) = mkPackageKey (packageKeySupported comp) (packageId pkg) - (map Info.packageKey (CD.nonSetupDeps deps)) [] + (map Info.libraryName (CD.nonSetupDeps deps)) + +-- | Extracts a library name from ReadyPackage, a common operation needed +-- to calculate build paths. +readyLibraryName :: Compiler -> ReadyPackage -> LibraryName +readyLibraryName comp ready@(ReadyPackage pkg _ _ _) = + packageKeyLibraryName (packageId pkg) (readyPackageKey comp ready) -- | Sometimes we need to convert a 'ReadyPackage' back to a diff --git a/cabal-install/tests/UnitTests/Distribution/Client/Dependency/Modular/DSL.hs b/cabal-install/tests/UnitTests/Distribution/Client/Dependency/Modular/DSL.hs index 66d16b13e6a0bbc2c695a668ba238e4271b9b8dc..e5e3dd6e5825adc7446b29e6c88fed5413933cc7 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/Dependency/Modular/DSL.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/Dependency/Modular/DSL.hs @@ -243,12 +243,14 @@ exInstPkgId ex = C.PackageIdentifier { , pkgVersion = Version [exInstVersion ex, 0, 0] [] } +exInstLibName :: ExampleInstalled -> C.LibraryName +exInstLibName ex = C.packageKeyLibraryName (exInstPkgId ex) (exInstKey ex) + exInstKey :: ExampleInstalled -> C.PackageKey exInstKey ex = C.mkPackageKey True (exInstPkgId ex) - (map exInstKey (exInstBuildAgainst ex)) - [] + (map exInstLibName (exInstBuildAgainst ex)) exAvIdx :: [ExampleAvailable] -> CI.PackageIndex.PackageIndex SourcePackage exAvIdx = CI.PackageIndex.fromList . map exAvSrcPkg