Skip to content

Commit

Permalink
Make --dependency accept a component too
Browse files Browse the repository at this point in the history
The old --dependency could only do --dependency=pkg=cid,
but with public sublibraries this will become insufficient.

Now there is the option to also specify a component name using
--dependency=pkg:component=cid
  • Loading branch information
fgaz committed Jun 27, 2018
1 parent 38c06d4 commit 5b27aa9
Show file tree
Hide file tree
Showing 6 changed files with 60 additions and 32 deletions.
43 changes: 24 additions & 19 deletions Cabal/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -434,7 +434,7 @@ configure (pkg_descr0, pbi) cfg = do
-- that is not possible to configure a test-suite to use one
-- version of a dependency, and the executable to use another.
(allConstraints :: [Dependency],
requiredDepsMap :: Map PackageName InstalledPackageInfo)
requiredDepsMap :: Map (PackageName, ComponentName) InstalledPackageInfo)
<- either (die' verbosity) return $
combinedConstraints (configConstraints cfg)
(configDependencies cfg)
Expand Down Expand Up @@ -862,7 +862,7 @@ dependencySatisfiable
-> PackageName
-> InstalledPackageIndex -- ^ installed set
-> Map PackageName (Maybe UnqualComponentName) -- ^ internal set
-> Map PackageName InstalledPackageInfo -- ^ required dependencies
-> Map (PackageName, ComponentName) InstalledPackageInfo -- ^ required dependencies
-> (Dependency -> Bool)
dependencySatisfiable
use_external_internal_deps
Expand All @@ -882,7 +882,7 @@ dependencySatisfiable
-- Except for internal deps, when we're NOT per-component mode;
-- those are just True.
then True
else depName `Map.member` requiredDepsMap
else (depName, CLibName) `Map.member` requiredDepsMap

| isInternalDep
= if use_external_internal_deps
Expand Down Expand Up @@ -1010,7 +1010,7 @@ configureDependencies
-> UseExternalInternalDeps
-> Map PackageName (Maybe UnqualComponentName) -- ^ internal packages
-> InstalledPackageIndex -- ^ installed packages
-> Map PackageName InstalledPackageInfo -- ^ required deps
-> Map (PackageName, ComponentName) InstalledPackageInfo -- ^ required deps
-> PackageDescription
-> ComponentRequestedSpec
-> IO [PreExistingComponent]
Expand Down Expand Up @@ -1184,7 +1184,7 @@ data FailedDependency = DependencyNotExists PackageName
selectDependency :: PackageId -- ^ Package id of current package
-> Map PackageName (Maybe UnqualComponentName)
-> InstalledPackageIndex -- ^ Installed packages
-> Map PackageName InstalledPackageInfo
-> Map (PackageName, ComponentName) InstalledPackageInfo
-- ^ Packages for which we have been given specific deps to
-- use
-> UseExternalInternalDeps -- ^ Are we configuring a
Expand Down Expand Up @@ -1220,7 +1220,7 @@ selectDependency pkgid internalIndex installedIndex requiredDepsMap

-- We have to look it up externally
do_external is_internal = do
ipi <- case Map.lookup dep_pkgname requiredDepsMap of
ipi <- case Map.lookup (dep_pkgname, CLibName) requiredDepsMap of
-- If we know the exact pkg to use, then use it.
Just pkginstance -> Right pkginstance
-- Otherwise we just pick an arbitrary instance of the latest version.
Expand Down Expand Up @@ -1355,10 +1355,10 @@ interpretPackageDbFlags userInstall specificDBs =
-- deps in the end. So we still need to remember which installed packages to
-- pick.
combinedConstraints :: [Dependency] ->
[(PackageName, ComponentId)] ->
[(PackageName, ComponentName, ComponentId)] ->
InstalledPackageIndex ->
Either String ([Dependency],
Map PackageName InstalledPackageInfo)
Map (PackageName, ComponentName) InstalledPackageInfo)
combinedConstraints constraints dependencies installedPackages = do

when (not (null badComponentIds)) $
Expand All @@ -1374,21 +1374,21 @@ combinedConstraints constraints dependencies installedPackages = do
allConstraints :: [Dependency]
allConstraints = constraints
++ [ thisPackageVersion (packageId pkg)
| (_, _, Just pkg) <- dependenciesPkgInfo ]
| (_, _, _, Just pkg) <- dependenciesPkgInfo ]

idConstraintMap :: Map PackageName InstalledPackageInfo
idConstraintMap :: Map (PackageName, ComponentName) InstalledPackageInfo
idConstraintMap = Map.fromList
-- NB: do NOT use the packageName from
-- dependenciesPkgInfo!
[ (pn, pkg)
| (pn, _, Just pkg) <- dependenciesPkgInfo ]
[ ((pn, cname), pkg)
| (pn, cname, _, Just pkg) <- dependenciesPkgInfo ]

-- The dependencies along with the installed package info, if it exists
dependenciesPkgInfo :: [(PackageName, ComponentId,
dependenciesPkgInfo :: [(PackageName, ComponentName, ComponentId,
Maybe InstalledPackageInfo)]
dependenciesPkgInfo =
[ (pkgname, cid, mpkg)
| (pkgname, cid) <- dependencies
[ (pkgname, cname, cid, mpkg)
| (pkgname, cname, cid) <- dependencies
, let mpkg = PackageIndex.lookupComponentId
installedPackages cid
]
Expand All @@ -1397,13 +1397,18 @@ combinedConstraints constraints dependencies installedPackages = do
-- (i.e. someone has written a hash) and didn't find it then it's
-- an error.
badComponentIds =
[ (pkgname, cid)
| (pkgname, cid, Nothing) <- dependenciesPkgInfo ]
[ (pkgname, cname, cid)
| (pkgname, cname, cid, Nothing) <- dependenciesPkgInfo ]

dispDependencies deps =
hsep [ text "--dependency="
<<>> quotes (disp pkgname <<>> char '=' <<>> disp cid)
| (pkgname, cid) <- deps ]
<<>> quotes
(disp pkgname
<<>> case cname of CSubLibName sublib -> ":" <<>> disp sublib
_ -> "" --XXX
<<>> char '='
<<>> disp cid)
| (pkgname, cname, cid) <- deps ]

-- -----------------------------------------------------------------------------
-- Configuring program dependencies
Expand Down
26 changes: 19 additions & 7 deletions Cabal/Distribution/Simple/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -102,8 +102,10 @@ import Distribution.Verbosity
import Distribution.Utils.NubList
import Distribution.Types.Dependency
import Distribution.Types.ComponentId
import Distribution.Types.ComponentName (ComponentName(..))
import Distribution.Types.Module
import Distribution.Types.PackageName
import Distribution.Types.UnqualComponentName (unUnqualComponentName)

import Distribution.Compat.Stack
import Distribution.Compat.Semigroup (Last' (..))
Expand Down Expand Up @@ -256,7 +258,7 @@ data ConfigFlags = ConfigFlags {
configStripLibs :: Flag Bool, -- ^Enable library stripping
configConstraints :: [Dependency], -- ^Additional constraints for
-- dependencies.
configDependencies :: [(PackageName, ComponentId)],
configDependencies :: [(PackageName, ComponentName, ComponentId)],
-- ^The packages depended on.
configInstantiateWith :: [(ModuleName, Module)],
-- ^ The requested Backpack instantiation. If empty, either this
Expand Down Expand Up @@ -645,9 +647,13 @@ configureOptions showOrParseArgs =
,option "" ["dependency"]
"A list of exact dependencies. E.g., --dependency=\"void=void-0.5.8-177d5cdf20962d0581fe2e4932a6c309\""
configDependencies (\v flags -> flags { configDependencies = v})
(reqArg "NAME=CID"
(reqArg "NAME[:COMPONENT_NAME]=CID"
(parsecToReadE (const "dependency expected") ((\x -> [x]) `fmap` parsecDependency))
(map (\x -> display (fst x) ++ "=" ++ display (snd x))))
(map (\(pn, cn, cid) ->
display pn ++ "="
++ case cn of CSubLibName sublib -> ":" ++ display sublib
_ -> "" --XXX
++ display cid)))

,option "" ["instantiate-with"]
"A mapping of signature names to concrete module instantiations."
Expand Down Expand Up @@ -729,12 +735,18 @@ showProfDetailLevelFlag :: Flag ProfDetailLevel -> [String]
showProfDetailLevelFlag NoFlag = []
showProfDetailLevelFlag (Flag dl) = [showProfDetailLevel dl]

parsecDependency :: ParsecParser (PackageName, ComponentId)
parsecDependency :: ParsecParser (PackageName, ComponentName, ComponentId)
parsecDependency = do
x <- parsec
pn <- parsec
cn <- P.option CLibName $ do
_ <- P.char ':'
ucn <- parsec
return $ if unUnqualComponentName ucn == unPackageName pn
then CLibName
else CSubLibName ucn
_ <- P.char '='
y <- parsec
return (x, y)
cid <- parsec
return (pn, cn, cid)

installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
installDirsOptions =
Expand Down
2 changes: 1 addition & 1 deletion cabal-install/Distribution/Client/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -402,7 +402,7 @@ configurePackage verbosity platform comp scriptOptions configFlags
-- depending on the Cabal version we are talking to.
configConstraints = [ thisPackageVersion srcid
| ConfiguredId srcid (Just PkgDesc.CLibName) _uid <- CD.nonSetupDeps deps ],
configDependencies = [ (packageName srcid, uid)
configDependencies = [ (packageName srcid, PkgDesc.CLibName, uid)
| ConfiguredId srcid (Just PkgDesc.CLibName) uid <- CD.nonSetupDeps deps ],
-- Use '--exact-configuration' if supported.
configExactConfiguration = toFlag True,
Expand Down
2 changes: 1 addition & 1 deletion cabal-install/Distribution/Client/Install.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1241,7 +1241,7 @@ installReadyPackage platform cinfo configFlags
configConstraints = [ thisPackageVersion srcid
| ConfiguredId srcid (Just PackageDescription.CLibName) _ipid
<- CD.nonSetupDeps deps ],
configDependencies = [ (packageName srcid, dep_ipid)
configDependencies = [ (packageName srcid, PackageDescription.CLibName, dep_ipid)
| ConfiguredId srcid (Just PackageDescription.CLibName) dep_ipid
<- CD.nonSetupDeps deps ],
-- Use '--exact-configuration' if supported.
Expand Down
1 change: 1 addition & 0 deletions cabal-install/Distribution/Client/ProjectPlanning.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3262,6 +3262,7 @@ setupHsConfigureFlags (ReadyPackage elab@ElaboratedConfiguredPackage{..})
| packageId elab == srcid
-> mkPackageName (unUnqualComponentName uqn)
_ -> packageName srcid,
CLibName,
cid)
| ConfiguredId srcid mb_cn cid <- elabLibDependencies elab ]
configConstraints =
Expand Down
18 changes: 14 additions & 4 deletions cabal-install/Distribution/Client/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,7 @@ import Distribution.Package
( PackageIdentifier, PackageName, packageName, packageVersion )
import Distribution.Types.Dependency
import Distribution.PackageDescription
( BuildType(..), RepoKind(..) )
( BuildType(..), RepoKind(..), ComponentName(..) )
import Distribution.System ( Platform )
import Distribution.Text
( Text(..), display )
Expand Down Expand Up @@ -464,7 +464,7 @@ filterConfigureFlags :: ConfigFlags -> Version -> ConfigFlags
filterConfigureFlags flags cabalLibVersion
-- NB: we expect the latest version to be the most common case,
-- so test it first.
| cabalLibVersion >= mkVersion [2,1,0] = flags_latest
| cabalLibVersion >= mkVersion [2,3,0] = flags_latest
-- The naming convention is that flags_version gives flags with
-- all flags *introduced* in version eliminated.
-- It is NOT the latest version of Cabal library that
Expand All @@ -482,14 +482,24 @@ filterConfigureFlags flags cabalLibVersion
| cabalLibVersion < mkVersion [1,23,0] = flags_1_23_0
| cabalLibVersion < mkVersion [1,25,0] = flags_1_25_0
| cabalLibVersion < mkVersion [2,1,0] = flags_2_1_0
| cabalLibVersion < mkVersion [2,3,0] = flags_2_3_0
| otherwise = flags_latest
where
flags_latest = flags {
flags_latest = flags {
-- Cabal < 2.3.0 does not understand --dependency=pkg:COMPONENT=cid
-- (public sublibraries)
configDependencies =
let isMainLib CLibName = True
isMainLib _ = False
in filter (\(_, c, _) -> isMainLib c) $ configDependencies flags
}

flags_2_3_0 = flags_latest {
-- Cabal >= 1.19.1 uses '--dependency' and does not need '--constraint'.
configConstraints = []
}

flags_2_1_0 = flags_latest {
flags_2_1_0 = flags_2_3_0 {
-- Cabal < 2.1 doesn't know about -v +timestamp modifier
configVerbosity = fmap verboseNoTimestamp (configVerbosity flags_latest)
-- Cabal < 2.1 doesn't know about --<enable|disable>-static
Expand Down

0 comments on commit 5b27aa9

Please sign in to comment.