diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal index 8d5b583f22260727a398d3c7c2c10023c446bbf8..98f10df1d7fd33a0113b7804a84a79cb7fee5a33 100644 --- a/Cabal/Cabal.cabal +++ b/Cabal/Cabal.cabal @@ -108,6 +108,17 @@ extra-source-files: tests/PackageTests/Configure/include/HsZlibConfig.h.in tests/PackageTests/Configure/zlib.buildinfo.in tests/PackageTests/Configure/zlib.cabal + tests/PackageTests/ConfigureComponent/Exe/Bad.hs + tests/PackageTests/ConfigureComponent/Exe/Exe.cabal + tests/PackageTests/ConfigureComponent/Exe/Good.hs + tests/PackageTests/ConfigureComponent/SubLib/Lib.cabal + tests/PackageTests/ConfigureComponent/SubLib/Lib.hs + tests/PackageTests/ConfigureComponent/SubLib/exe/Exe.hs + tests/PackageTests/ConfigureComponent/Test/Lib.hs + tests/PackageTests/ConfigureComponent/Test/Test.cabal + tests/PackageTests/ConfigureComponent/Test/testlib/TestLib.hs + tests/PackageTests/ConfigureComponent/Test/testlib/testlib.cabal + tests/PackageTests/ConfigureComponent/Test/tests/Test.hs tests/PackageTests/CopyAssumeDepsUpToDate/CopyAssumeDepsUpToDate.cabal tests/PackageTests/CopyAssumeDepsUpToDate/Main.hs tests/PackageTests/CopyAssumeDepsUpToDate/P.hs diff --git a/Cabal/Distribution/PackageDescription/Configuration.hs b/Cabal/Distribution/PackageDescription/Configuration.hs index 74d5c03b4db63a28e4af85904206195deb934b46..e72f5d67135df7d8ef52b546b34a945355625fd7 100644 --- a/Cabal/Distribution/PackageDescription/Configuration.hs +++ b/Cabal/Distribution/PackageDescription/Configuration.hs @@ -421,11 +421,14 @@ overallDependencies enabled (TargetSet targets) = mconcat depss where (depss, _) = unzip $ filter (removeDisabledSections . snd) targets removeDisabledSections :: PDTagged -> Bool - removeDisabledSections (Lib l) = componentEnabled enabled (CLib l) - removeDisabledSections (SubLib _ l) = componentEnabled enabled (CLib l) - removeDisabledSections (Exe _ e) = componentEnabled enabled (CExe e) - removeDisabledSections (Test _ t) = componentEnabled enabled (CTest t) - removeDisabledSections (Bench _ b) = componentEnabled enabled (CBench b) + -- UGH. The embedded componentName in the 'Component's here is + -- BLANK. I don't know whose fault this is but I'll use the tag + -- instead. -- ezyang + removeDisabledSections (Lib _) = componentNameEnabled enabled CLibName + removeDisabledSections (SubLib t _) = componentNameEnabled enabled (CSubLibName t) + removeDisabledSections (Exe t _) = componentNameEnabled enabled (CExeName t) + removeDisabledSections (Test t _) = componentNameEnabled enabled (CTestName t) + removeDisabledSections (Bench t _) = componentNameEnabled enabled (CBenchName t) removeDisabledSections PDNull = True -- Apply extra constraints to a dependency map. diff --git a/Cabal/Distribution/Simple.hs b/Cabal/Distribution/Simple.hs index b0acbde5e8e4fff44ebd16bd0063b797fe5b81bf..90d3b04f8fa3eba4dfeba3e4a705388bed309cd6 100644 --- a/Cabal/Distribution/Simple.hs +++ b/Cabal/Distribution/Simple.hs @@ -579,7 +579,6 @@ defaultUserHooks = autoconfUserHooks { -- https://github.com/haskell/cabal/issues/158 where oldCompatPostConf args flags pkg_descr lbi = do let verbosity = fromFlag (configVerbosity flags) - noExtraFlags args confExists <- doesFileExist "configure" when confExists $ runConfigureScript verbosity @@ -610,7 +609,6 @@ autoconfUserHooks where defaultPostConf :: Args -> ConfigFlags -> PackageDescription -> LocalBuildInfo -> IO () defaultPostConf args flags pkg_descr lbi = do let verbosity = fromFlag (configVerbosity flags) - noExtraFlags args confExists <- doesFileExist "configure" if confExists then runConfigureScript verbosity diff --git a/Cabal/Distribution/Simple/BuildTarget.hs b/Cabal/Distribution/Simple/BuildTarget.hs index f0508680872b847be35f3c8487039b4382b47a68..4b89bbfb3c3d427ca733331691fa4c9e124de23c 100644 --- a/Cabal/Distribution/Simple/BuildTarget.hs +++ b/Cabal/Distribution/Simple/BuildTarget.hs @@ -12,6 +12,7 @@ module Distribution.Simple.BuildTarget ( -- * Main interface readTargetInfos, + readBuildTargets, -- in case you don't have LocalBuildInfo -- * Build targets BuildTarget(..), @@ -998,3 +999,7 @@ checkBuildTargets verbosity pkg_descr lbi targets = do formatReason cn DisabledAllBenchmarks = "Cannot process the " ++ cn ++ " because benchmarks are not " ++ "enabled. Re-run configure with the flag --enable-benchmarks" + formatReason cn (DisabledAllButOne cn') = + "Cannot process the " ++ cn ++ " because this package was " + ++ "configured only to build " ++ cn' ++ ". Re-run configure " + ++ "with the argument " ++ cn diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs index 72bfd89eaa3ba8df744e6ff31efc572ec89efe69..55ab9e9f5233e433dd656f8ec3297f73edb9e3bd 100644 --- a/Cabal/Distribution/Simple/Configure.hs +++ b/Cabal/Distribution/Simple/Configure.hs @@ -69,10 +69,12 @@ import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.Simple.PackageIndex (InstalledPackageIndex) import Distribution.PackageDescription as PD hiding (Flag) import Distribution.ModuleName +import Distribution.PackageDescription.PrettyPrint import Distribution.PackageDescription.Configuration import Distribution.PackageDescription.Check hiding (doesFileExist) import Distribution.Simple.Program import Distribution.Simple.Setup as Setup +import Distribution.Simple.BuildTarget import qualified Distribution.Simple.InstallDirs as InstallDirs import Distribution.Simple.LocalBuildInfo import Distribution.Types.LocalBuildInfo @@ -104,6 +106,7 @@ import Data.Either ( partitionEithers ) import qualified Data.Set as Set import qualified Data.Map as Map +import qualified Data.Maybe as Maybe import Numeric ( showIntAtBase ) import System.Directory ( doesFileExist, createDirectoryIfMissing, getTemporaryDirectory ) @@ -320,7 +323,32 @@ configure (pkg_descr0', pbi) cfg = do (maybe RelaxDepsNone unAllowNewer $ configAllowNewer cfg) pkg_descr0' - setupMessage verbosity "Configuring" (packageId pkg_descr0) + -- Determine the component we are configuring, if a user specified + -- one on the command line. We use a fake, flattened version of + -- the package since at this point, we're not really sure what + -- components we *can* configure. @Nothing@ means that we should + -- configure everything (the old behavior). + (mb_cname :: Maybe ComponentName) <- do + let flat_pkg_descr = flattenPackageDescription pkg_descr0 + targets <- readBuildTargets flat_pkg_descr (configArgs cfg) + -- TODO: bleat if you use the module/file syntax + let targets' = [ cname | BuildTargetComponent cname <- targets ] + case targets' of + _ | null (configArgs cfg) -> return Nothing + [cname] -> return (Just cname) + [] -> die "No valid component targets found" + _ -> die "Can only configure either single component or all of them" + + let use_external_internal_deps = isJust mb_cname + case mb_cname of + Nothing -> setupMessage verbosity "Configuring" (packageId pkg_descr0) + Just cname -> notice verbosity + ("Configuring component " ++ display cname ++ + " from " ++ display (packageId pkg_descr0)) + + -- configCID is only valid for per-component configure + when (isJust (flagToMaybe (configCID cfg)) && isNothing mb_cname) $ + die "--cid is only supported for per-component configure" checkDeprecatedFlags verbosity cfg checkExactConfiguration pkg_descr0 cfg @@ -360,17 +388,22 @@ configure (pkg_descr0', pbi) cfg = do <- getInstalledPackages (lessVerbose verbosity) comp packageDbs programsConfig - -- An approximate InstalledPackageIndex of all (possible) internal libraries. - -- This database is used to bootstrap the process before we know precisely - -- what these libraries are supposed to be. - let internalPackageSet :: InstalledPackageIndex + -- The set of package names which are "shadowed" by internal + -- packages, and which component they map to + let internalPackageSet :: Map PackageName ComponentName internalPackageSet = getInternalPackages pkg_descr0 -- Make a data structure describing what components are enabled. let enabled :: ComponentEnabledSpec - enabled = ComponentEnabledSpec - { testsEnabled = fromFlag (configTests cfg) - , benchmarksEnabled = fromFlag (configBenchmarks cfg) } + enabled = case mb_cname of + Just cname -> OneComponentEnabledSpec cname + Nothing -> ComponentEnabledSpec + { testsEnabled = fromFlag (configTests cfg) + , benchmarksEnabled = fromFlag (configBenchmarks cfg) } + -- Some sanity checks related to enabling components. + when (isJust mb_cname && (fromFlag (configTests cfg) || fromFlag (configBenchmarks cfg))) $ + die $ "--enable-tests/--enable-benchmarks are incompatible with" ++ + " explicitly specifying a component to configure." -- allConstraints: The set of all 'Dependency's we have. Used ONLY -- to 'configureFinalizedPackage'. @@ -413,6 +446,7 @@ configure (pkg_descr0', pbi) cfg = do allConstraints (dependencySatisfiable (fromFlagOrDefault False (configExactConfiguration cfg)) + (packageVersion pkg_descr0) installedPackageSet internalPackageSet requiredDepsMap) @@ -420,13 +454,25 @@ configure (pkg_descr0', pbi) cfg = do compPlatform pkg_descr0 + debug verbosity $ "Finalized package description:\n" + ++ showPackageDescription pkg_descr + -- NB: showPackageDescription does not display the AWFUL HACK GLOBAL + -- buildDepends, so we have to display it separately. See #2066 + -- Some day, we should eliminate this, so that + -- configureFinalizedPackage returns the set of overall dependencies + -- separately. Then 'configureDependencies' and + -- 'Distribution.PackageDescription.Check' need to be adjusted + -- accordingly. + debug verbosity $ "Finalized build-depends: " + ++ intercalate ", " (map display (buildDepends pkg_descr)) + checkCompilerProblems comp pkg_descr checkPackageProblems verbosity pkg_descr0 (updatePackageDescription pbi pkg_descr) -- The list of 'InstalledPackageInfo' recording the selected -- dependencies... - -- internalPkgDeps: ...on internal packages (these are fake!) + -- internalPkgDeps: ...on internal packages -- externalPkgDeps: ...on external packages -- -- Invariant: For any package name, there is at most one package @@ -442,6 +488,7 @@ configure (pkg_descr0', pbi) cfg = do externalPkgDeps :: [InstalledPackageInfo]) <- configureDependencies verbosity + use_external_internal_deps internalPackageSet installedPackageSet requiredDepsMap @@ -514,7 +561,8 @@ configure (pkg_descr0', pbi) cfg = do -- -- TODO: Move this into a helper function. defaultDirs :: InstallDirTemplates - <- defaultInstallDirs (compilerFlavor comp) + <- defaultInstallDirs' use_external_internal_deps + (compilerFlavor comp) (fromFlag (configUserInstall cfg)) (hasLibs pkg_descr) let installDirs :: InstallDirTemplates @@ -570,10 +618,11 @@ configure (pkg_descr0', pbi) cfg = do -- From there, we build a ComponentLocalBuildInfo for each of the -- components, which lets us actually build each component. buildComponents <- - case mkComponentsGraph enabled pkg_descr internalPkgDeps of + case mkComponentsGraph enabled pkg_descr internalPackageSet of Left componentCycle -> reportComponentCycle componentCycle Right comps -> - mkComponentsLocalBuildInfo cfg comp packageDependsIndex pkg_descr + mkComponentsLocalBuildInfo cfg use_external_internal_deps comp + packageDependsIndex pkg_descr internalPkgDeps externalPkgDeps comps (configConfigurationsFlags cfg) @@ -780,40 +829,29 @@ checkExactConfiguration pkg_descr0 cfg = do -- does the resolution of conditionals, and it takes internalPackageSet -- as part of its input. getInternalPackages :: GenericPackageDescription - -> InstalledPackageIndex + -> Map PackageName ComponentName getInternalPackages pkg_descr0 = + -- TODO: some day, executables will be fair game here too! let pkg_descr = flattenPackageDescription pkg_descr0 - mkInternalPackage lib = emptyInstalledPackageInfo { - --TODO: should use a per-compiler method to map the source - -- package ID into an installed package id we can use - -- for the internal package set. What we do here - -- is skeevy, but we're highly unlikely to accidentally - -- shadow something legitimate. - Installed.installedUnitId = mkUnitId n, - -- NB: we TEMPORARILY set the package name to be the - -- library name. When we actually register, it won't - -- look like this; this is just so that internal - -- build-depends get resolved correctly. - Installed.sourcePackageId = PackageIdentifier (PackageName n) - (pkgVersion (package pkg_descr)) - } - where n = case libName lib of - Nothing -> display (packageName pkg_descr) - Just n' -> n' - in PackageIndex.fromList (map mkInternalPackage (allLibraries pkg_descr)) - - --- | Returns true if a dependency is satisfiable. This is to be passed + f lib = case libName lib of + Nothing -> (packageName pkg_descr, CLibName) + Just n' -> (PackageName n', CSubLibName n') + in Map.fromList (map f (allLibraries pkg_descr)) + +-- | Returns true if a dependency is satisfiable. This function +-- may report a dependency satisfiable even when it is not, +-- but not vice versa. This is to be passed -- to finalizePD. dependencySatisfiable :: Bool + -> Version -> InstalledPackageIndex -- ^ installed set - -> InstalledPackageIndex -- ^ internal set + -> Map PackageName ComponentName -- ^ internal set -> Map PackageName InstalledPackageInfo -- ^ required dependencies -> (Dependency -> Bool) dependencySatisfiable - exact_config installedPackageSet internalPackageSet requiredDepsMap - d@(Dependency depName _) + exact_config pkg_ver installedPackageSet internalPackageSet requiredDepsMap + d@(Dependency depName verRange) | exact_config = -- When we're given '--exact-configuration', we assume that all -- dependencies and flags are exactly specified on the command @@ -827,17 +865,31 @@ dependencySatisfiable -- -- (However, note that internal deps don't have to be -- specified!) + -- + -- NB: Just like the case below, we might incorrectly + -- determine an external internal dep is satisfiable + -- when it actually isn't. (depName `Map.member` requiredDepsMap) || isInternalDep + | isInternalDep + , pkg_ver `withinRange` verRange = + -- If a 'PackageName' is defined by an internal component, + -- and the user didn't specify a version range which is + -- incompatible with the package version, the dep is + -- satisfiable (and we are going to use the internal + -- dependency.) Note that this doesn't mean we are + -- actually going to SUCCEED when we configure the package, + -- if UseExternalInternalDeps is True. NB: if + -- the version bound fails we want to fall through to the + -- next case. + True + | otherwise = - -- Normal operation: just look up dependency in the combined + -- Normal operation: just look up dependency in the -- package index. - not . null . PackageIndex.lookupDependency pkgs $ d + not . null . PackageIndex.lookupDependency installedPackageSet $ d where - -- NB: Prefer the INTERNAL package set - pkgs = PackageIndex.merge installedPackageSet internalPackageSet - isInternalDep = not . null - $ PackageIndex.lookupDependency internalPackageSet d + isInternalDep = Map.member depName internalPackageSet -- | Relax the dependencies of this package if needed. relaxPackageDeps :: (VersionRange -> VersionRange) @@ -939,22 +991,26 @@ checkCompilerProblems comp pkg_descr = do die $ "Your compiler does not support module re-exports. To use " ++ "this feature you probably must use GHC 7.9 or later." +type UseExternalInternalDeps = Bool + -- | Select dependencies for the package. configureDependencies :: Verbosity - -> InstalledPackageIndex -- ^ internal packages + -> UseExternalInternalDeps + -> Map PackageName ComponentName -- ^ internal packages -> InstalledPackageIndex -- ^ installed packages -> Map PackageName InstalledPackageInfo -- ^ required deps -> PackageDescription -> IO ([PackageId], [InstalledPackageInfo]) -configureDependencies verbosity +configureDependencies verbosity use_external_internal_deps internalPackageSet installedPackageSet requiredDepsMap pkg_descr = do let selectDependencies :: [Dependency] -> ([FailedDependency], [ResolvedDependency]) selectDependencies = partitionEithers - . map (selectDependency internalPackageSet installedPackageSet - requiredDepsMap) + . map (selectDependency (package pkg_descr) + internalPackageSet installedPackageSet + requiredDepsMap use_external_internal_deps) (failedDeps, allPkgDeps) = selectDependencies (buildDepends pkg_descr) @@ -1079,23 +1135,34 @@ reportProgram verbosity prog (Just configuredProg) hackageUrl :: String hackageUrl = "http://hackage.haskell.org/package/" -data ResolvedDependency = ExternalDependency Dependency InstalledPackageInfo - | InternalDependency Dependency PackageId -- should be a - -- lib name +data ResolvedDependency + -- | An external dependency from the package database, OR an + -- internal dependency which we are getting from the package + -- database. + = ExternalDependency Dependency InstalledPackageInfo + -- | An internal dependency ('PackageId' should be a library name) + -- which we are going to have to build. (The + -- 'PackageId' here is a hack to get a modest amount of + -- polymorphism out of the 'Package' typeclass.) + | InternalDependency Dependency PackageId data FailedDependency = DependencyNotExists PackageName + | DependencyMissingInternal PackageName PackageName | DependencyNoVersion Dependency -- | Test for a package dependency and record the version we have installed. -selectDependency :: InstalledPackageIndex -- ^ Internally defined packages +selectDependency :: PackageId -- ^ Package id of current package + -> Map PackageName ComponentName -> InstalledPackageIndex -- ^ Installed packages -> Map PackageName InstalledPackageInfo -- ^ Packages for which we have been given specific deps to -- use + -> UseExternalInternalDeps -- ^ Are we configuring a single component? -> Dependency -> Either FailedDependency ResolvedDependency -selectDependency internalIndex installedIndex requiredDepsMap - dep@(Dependency pkgname vr) = +selectDependency pkgid internalIndex installedIndex requiredDepsMap + use_external_internal_deps + dep@(Dependency dep_pkgname vr) = -- If the dependency specification matches anything in the internal package -- index, then we prefer that match to anything in the second. -- For example: @@ -1110,19 +1177,32 @@ selectDependency internalIndex installedIndex requiredDepsMap -- We want "build-depends: MyLibrary" always to match the internal library -- even if there is a newer installed library "MyLibrary-0.2". -- However, "build-depends: MyLibrary >= 0.2" should match the installed one. - case PackageIndex.lookupPackageName internalIndex pkgname of - [(_,[pkg])] | packageVersion pkg `withinRange` vr - -> Right $ InternalDependency dep (packageId pkg) - - _ -> case Map.lookup pkgname requiredDepsMap of + case Map.lookup dep_pkgname internalIndex of + Just cname | packageVersion pkgid `withinRange` vr + -> if use_external_internal_deps + then do_external (Just cname) + else do_internal + _ -> do_external Nothing + where + do_internal = Right (InternalDependency dep + (PackageIdentifier dep_pkgname (packageVersion pkgid))) + do_external is_internal = case Map.lookup dep_pkgname requiredDepsMap of -- If we know the exact pkg to use, then use it. Just pkginstance -> Right (ExternalDependency dep pkginstance) -- Otherwise we just pick an arbitrary instance of the latest version. - Nothing -> case PackageIndex.lookupDependency installedIndex dep of - [] -> Left $ DependencyNotExists pkgname + Nothing -> case PackageIndex.lookupDependency installedIndex dep' of + [] -> Left $ + case is_internal of + Just cname -> DependencyMissingInternal dep_pkgname + (computeCompatPackageName (packageName pkgid) cname) + Nothing -> DependencyNotExists dep_pkgname pkgs -> Right $ ExternalDependency dep $ case last pkgs of (_ver, pkginstances) -> head pkginstances + where + dep' | Just cname <- is_internal + = Dependency (computeCompatPackageName (packageName pkgid) cname) vr + | otherwise = dep reportSelectedDependencies :: Verbosity -> [ResolvedDependency] -> IO () @@ -1146,6 +1226,11 @@ reportFailedDependencies failed = ++ "Perhaps you need to download and install it from\n" ++ hackageUrl ++ display pkgname ++ "?" + reportFailedDependency (DependencyMissingInternal pkgname real_pkgname) = + "internal dependency " ++ display pkgname ++ " not installed.\n" + ++ "Perhaps you need to configure and install it first?\n" + ++ "(Munged package name we searched for was " ++ display real_pkgname ++ ")" + reportFailedDependency (DependencyNoVersion dep) = "cannot satisfy dependency " ++ display (simplifyDependency dep) ++ "\n" @@ -1256,12 +1341,6 @@ combinedConstraints constraints dependencies installedPackages = do $+$ nest 4 (dispDependencies badUnitIds) $+$ text "however the given installed package instance does not exist." - when (not (null badNames)) $ - Left $ render $ text "The following package dependencies were requested" - $+$ nest 4 (dispDependencies badNames) - $+$ text ("however the installed package's name does not match " - ++ "the name given.") - --TODO: we don't check that all dependencies are used! return (allConstraints, idConstraintMap) @@ -1294,15 +1373,6 @@ combinedConstraints constraints dependencies installedPackages = do [ (pkgname, ipkgid) | (pkgname, ipkgid, Nothing) <- dependenciesPkgInfo ] - -- If someone has written e.g. - -- --dependency="foo=MyOtherLib-1.0-07...5bf30" then they have - -- probably made a mistake. - badNames = - [ (requestedPkgName, ipkgid) - | (requestedPkgName, ipkgid, Just pkg) <- dependenciesPkgInfo - , let foundPkgName = packageName pkg - , requestedPkgName /= foundPkgName ] - dispDependencies deps = hsep [ text "--dependency=" <<>> quotes (disp pkgname <<>> char '=' <<>> disp ipkgid) @@ -1492,14 +1562,12 @@ configCompilerAux = fmap (\(a,_,b) -> (a,b)) . configCompilerAuxEx -- libraries are considered internal), create a graph of dependencies -- between the components. This is NOT necessarily the build order -- (although it is in the absence of Backpack.) --- --- TODO: tighten up the type of 'internalPkgDeps' mkComponentsGraph :: ComponentEnabledSpec -> PackageDescription - -> [PackageId] + -> Map PackageName ComponentName -> Either [ComponentName] [(Component, [ComponentName])] -mkComponentsGraph enabled pkg_descr internalPkgDeps = +mkComponentsGraph enabled pkg_descr internalPackageSet = let g = Graph.fromList [ N c (componentName c) (componentDeps c) | c <- pkgBuildableComponents pkg_descr , componentEnabled enabled c ] @@ -1514,12 +1582,9 @@ mkComponentsGraph enabled pkg_descr internalPkgDeps = , toolname `elem` map exeName (executables pkg_descr) ] - ++ [ if pkgname == packageName pkg_descr - then CLibName - else CSubLibName toolname - | Dependency pkgname@(PackageName toolname) _ - <- targetBuildDepends bi - , pkgname `elem` map packageName internalPkgDeps ] + ++ [ cname + | Dependency pkgname _ <- targetBuildDepends bi + , cname <- Maybe.maybeToList (Map.lookup pkgname internalPackageSet) ] where bi = componentBuildInfo component @@ -1535,13 +1600,14 @@ reportComponentCycle cnames = -- specify a more detailed IPID via the @--ipid@ flag if necessary. computeComponentId :: Flag String + -> Flag ComponentId -> PackageIdentifier -> ComponentName -- TODO: careful here! -> [ComponentId] -- IPIDs of the component dependencies -> FlagAssignment -> ComponentId -computeComponentId mb_explicit pid cname dep_ipids flagAssignment = do +computeComponentId mb_ipid mb_cid pid cname dep_ipids flagAssignment = -- show is found to be faster than intercalate and then replacement of -- special character used in intercalating. We cannot simply hash by -- doubly concating list, as it just flatten out the nested list, so @@ -1559,13 +1625,15 @@ computeComponentId mb_explicit pid cname dep_ipids flagAssignment = do -- Hack to reuse install dirs machinery -- NB: no real IPID available at this point where env = packageTemplateEnv pid (mkUnitId "") - actual_base = case mb_explicit of - Flag cid0 -> explicit_base cid0 + actual_base = case mb_ipid of + Flag ipid0 -> explicit_base ipid0 NoFlag -> generated_base - ComponentId $ actual_base - ++ (case componentNameString cname of - Nothing -> "" - Just s -> "-" ++ s) + in case mb_cid of + Flag cid -> cid + NoFlag -> ComponentId $ actual_base + ++ (case componentNameString cname of + Nothing -> "" + Just s -> "-" ++ s) hashToBase62 :: String -> String hashToBase62 s = showFingerprint $ fingerprintString s @@ -1692,6 +1760,7 @@ computeCompatPackageKey comp pkg_name pkg_version (SimpleUnitId (ComponentId str | otherwise = str mkComponentsLocalBuildInfo :: ConfigFlags + -> UseExternalInternalDeps -> Compiler -> InstalledPackageIndex -> PackageDescription @@ -1700,7 +1769,7 @@ mkComponentsLocalBuildInfo :: ConfigFlags -> [(Component, [ComponentName])] -> FlagAssignment -> IO [ComponentLocalBuildInfo] -mkComponentsLocalBuildInfo cfg comp installedPackages pkg_descr +mkComponentsLocalBuildInfo cfg use_external_internal comp installedPackages pkg_descr internalPkgDeps externalPkgDeps graph flagAssignment = foldM go [] graph @@ -1774,8 +1843,7 @@ mkComponentsLocalBuildInfo cfg comp installedPackages pkg_descr } where - -- TODO configIPID should have name changed - cid = computeComponentId (configIPID cfg) (package pkg_descr) + cid = computeComponentId (configIPID cfg) (configCID cfg) (package pkg_descr) (componentName component) (getDeps (componentName component)) flagAssignment @@ -1818,6 +1886,7 @@ mkComponentsLocalBuildInfo cfg comp installedPackages pkg_descr dedup = Map.toList . Map.fromList -- TODO: this should include internal deps too + -- NB: This works correctly in per-component mode getDeps :: ComponentName -> [ComponentId] getDeps cname = let externalPkgs @@ -1827,7 +1896,11 @@ mkComponentsLocalBuildInfo cfg comp installedPackages pkg_descr in map Installed.installedComponentId externalPkgs selectSubset :: Package pkg => BuildInfo -> [pkg] -> [pkg] - selectSubset bi pkgs = + selectSubset bi pkgs + -- No need to subset for one-component config: deps + -- is precisely what we want + | use_external_internal = pkgs + | otherwise = [ pkg | pkg <- pkgs, packageName pkg `elem` names bi ] names :: BuildInfo -> [PackageName] diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs index 3e7cd63419723aee3fca7edfb63f4cb654d46f38..af2309315b36754dbcc3f93dfeff9c19d9c24fd0 100644 --- a/Cabal/Distribution/Simple/GHC.hs +++ b/Cabal/Distribution/Simple/GHC.hs @@ -1138,20 +1138,17 @@ installLib :: Verbosity -> Library -> ComponentLocalBuildInfo -> IO () -installLib verbosity lbi targetDir dynlibTargetDir _builtDir pkg lib clbi = do +installLib verbosity lbi targetDir dynlibTargetDir _builtDir _pkg lib clbi = do -- copy .hi files over: - whenRegistered $ do - whenVanilla $ copyModuleFiles "hi" - whenProf $ copyModuleFiles "p_hi" - whenShared $ copyModuleFiles "dyn_hi" + whenVanilla $ copyModuleFiles "hi" + whenProf $ copyModuleFiles "p_hi" + whenShared $ copyModuleFiles "dyn_hi" -- copy the built library files over: - whenRegistered $ do - whenVanilla $ installOrdinary builtDir targetDir vanillaLibName - whenProf $ installOrdinary builtDir targetDir profileLibName - whenGHCi $ installOrdinary builtDir targetDir ghciLibName - whenRegisteredOrDynExecutable $ do - whenShared $ installShared builtDir dynlibTargetDir sharedLibName + whenVanilla $ installOrdinary builtDir targetDir vanillaLibName + whenProf $ installOrdinary builtDir targetDir profileLibName + whenGHCi $ installOrdinary builtDir targetDir ghciLibName + whenShared $ installShared builtDir dynlibTargetDir sharedLibName where builtDir = componentBuildDir lbi clbi @@ -1189,17 +1186,6 @@ installLib verbosity lbi targetDir dynlibTargetDir _builtDir pkg lib clbi = do whenGHCi = when (hasLib && withGHCiLib lbi) whenShared = when (hasLib && withSharedLib lbi) - -- Some files (e.g. interface files) are completely unnecessary when - -- we are not actually going to register the library. A library is - -- not registered if there is no "public library", e.g. in the case - -- that we have an internal library and executables, but no public - -- library. - whenRegistered = when (hasPublicLib pkg) - - -- However, we must always install dynamic libraries when linking - -- dynamic executables, because we'll try to load them! - whenRegisteredOrDynExecutable = when (hasPublicLib pkg || (hasExes pkg && withDynExe lbi)) - -- ----------------------------------------------------------------------------- -- Registering diff --git a/Cabal/Distribution/Simple/InstallDirs.hs b/Cabal/Distribution/Simple/InstallDirs.hs index 46a91307b08c827380fe9d5e4f4b62159cf00d44..fe282407071b914e273ae076a83b99876a8679a7 100644 --- a/Cabal/Distribution/Simple/InstallDirs.hs +++ b/Cabal/Distribution/Simple/InstallDirs.hs @@ -25,6 +25,7 @@ module Distribution.Simple.InstallDirs ( InstallDirs(..), InstallDirTemplates, defaultInstallDirs, + defaultInstallDirs', combineInstallDirs, absoluteInstallDirs, CopyDest(..), @@ -156,7 +157,17 @@ type InstallDirTemplates = InstallDirs PathTemplate -- Default installation directories defaultInstallDirs :: CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates -defaultInstallDirs comp userInstall _hasLibs = do +defaultInstallDirs = defaultInstallDirs' False + +defaultInstallDirs' :: Bool {- use external internal deps -} + -> CompilerFlavor -> Bool -> Bool -> IO InstallDirTemplates +defaultInstallDirs' True comp userInstall hasLibs = do + dflt <- defaultInstallDirs' False comp userInstall hasLibs + -- Be a bit more hermetic about per-component installs + return dflt { datasubdir = toPathTemplate $ "$abi" </> "$libname", + docdir = toPathTemplate $ "$datadir" </> "doc" </> "$abi" </> "$libname" + } +defaultInstallDirs' False comp userInstall _hasLibs = do installPrefix <- if userInstall then getAppUserDataDirectory "cabal" diff --git a/Cabal/Distribution/Simple/Register.hs b/Cabal/Distribution/Simple/Register.hs index 8425be818742ed4c83765ef88e3033453c628617..d3f7702205d45d76d2e171b20d6dcca1e80ad7e3 100644 --- a/Cabal/Distribution/Simple/Register.hs +++ b/Cabal/Distribution/Simple/Register.hs @@ -88,12 +88,13 @@ import qualified Data.ByteString.Lazy.Char8 as BS.Char8 register :: PackageDescription -> LocalBuildInfo -> RegisterFlags -- ^Install in the user's database?; verbose -> IO () -register pkg_descr lbi flags = when (hasPublicLib pkg_descr) doRegister +register pkg_descr lbi flags = + -- Duncan originally asked for us to not register/install files + -- when there was no public library. But with per-component + -- configure, we legitimately need to install internal libraries + -- so that we can get them. So just unconditionally install. + doRegister where - -- We do NOT register libraries outside of the inplace database - -- if there is no public library, since no one else can use it - -- usefully (they're not public.) If we start supporting scoped - -- packages, we'll have to relax this. doRegister = do targets <- readTargetInfos verbosity pkg_descr lbi (regArgs flags) diff --git a/Cabal/Distribution/Simple/Setup.hs b/Cabal/Distribution/Simple/Setup.hs index ddd7fc8da32c9951f15ddd53ee132d3dc7b49eba..39667819be4761b4f9d27ec473d98619c406c0da 100644 --- a/Cabal/Distribution/Simple/Setup.hs +++ b/Cabal/Distribution/Simple/Setup.hs @@ -391,6 +391,7 @@ data ConfigFlags = ConfigFlags { -- frameworks (OS X only) configExtraIncludeDirs :: [FilePath], -- ^ path to search for header files configIPID :: Flag String, -- ^ explicit IPID to be used + configCID :: Flag ComponentId, -- ^ explicit CID to be used configDistPref :: Flag FilePath, -- ^"dist" prefix configCabalFilePath :: Flag FilePath, -- ^ Cabal file to use @@ -677,6 +678,11 @@ configureOptions showOrParseArgs = configIPID (\v flags -> flags {configIPID = v}) (reqArgFlag "IPID") + ,option "" ["cid"] + "Installed component ID to compile this component as" + (fmap display . configCID) (\v flags -> flags {configCID = fmap ComponentId v}) + (reqArgFlag "CID") + ,option "" ["extra-lib-dirs"] "A list of directories to search for external libraries" configExtraLibDirs (\v flags -> flags {configExtraLibDirs = v}) diff --git a/Cabal/Distribution/Simple/UserHooks.hs b/Cabal/Distribution/Simple/UserHooks.hs index 5f0fd21ed10ece497bff4f5a2efa4a422a7451ef..b3ba6cf9b99b2d9247b35b628badb70d85fdf495 100644 --- a/Cabal/Distribution/Simple/UserHooks.hs +++ b/Cabal/Distribution/Simple/UserHooks.hs @@ -164,7 +164,7 @@ emptyUserHooks readDesc = return Nothing, hookedPreProcessors = [], hookedPrograms = [], - preConf = rn, + preConf = rn', confHook = (\_ _ -> return (error "No local build info generated during configure. Over-ride empty configure hook.")), postConf = ru, preBuild = rn', diff --git a/Cabal/Distribution/Types/ComponentEnabledSpec.hs b/Cabal/Distribution/Types/ComponentEnabledSpec.hs index 78227cd1779e44f7d700dd6b1f66eed53301033f..b78259cddfbb15f729d23465f2d5bafdfc5bac95 100644 --- a/Cabal/Distribution/Types/ComponentEnabledSpec.hs +++ b/Cabal/Distribution/Types/ComponentEnabledSpec.hs @@ -15,6 +15,7 @@ module Distribution.Types.ComponentEnabledSpec ( import Prelude () import Distribution.Compat.Prelude +import Distribution.Text import Distribution.Types.Component -- TODO: maybe remove me? import Distribution.Types.ComponentName @@ -50,10 +51,9 @@ import Distribution.Types.ComponentName -- -- @since 2.0.0.0 data ComponentEnabledSpec - = ComponentEnabledSpec { - testsEnabled :: Bool, - benchmarksEnabled :: Bool - } + = ComponentEnabledSpec { testsEnabled :: Bool, + benchmarksEnabled :: Bool } + | OneComponentEnabledSpec ComponentName deriving (Generic, Read, Show) instance Binary ComponentEnabledSpec @@ -91,11 +91,16 @@ componentDisabledReason enabled comp -- @since 2.0.0.0 componentNameDisabledReason :: ComponentEnabledSpec -> ComponentName -> Maybe ComponentDisabledReason -componentNameDisabledReason enabled (CTestName _) - | not (testsEnabled enabled) = Just DisabledAllTests -componentNameDisabledReason enabled (CBenchName _) - | not (benchmarksEnabled enabled) = Just DisabledAllBenchmarks -componentNameDisabledReason _ _ = Nothing +componentNameDisabledReason + ComponentEnabledSpec{ testsEnabled = False } (CTestName _) + = Just DisabledAllTests +componentNameDisabledReason + ComponentEnabledSpec{ benchmarksEnabled = False } (CBenchName _) + = Just DisabledAllBenchmarks +componentNameDisabledReason ComponentEnabledSpec{} _ = Nothing +componentNameDisabledReason (OneComponentEnabledSpec cname) c + | c == cname = Nothing + | otherwise = Just (DisabledAllButOne (display cname)) -- | A reason explaining why a component is disabled. -- @@ -103,3 +108,4 @@ componentNameDisabledReason _ _ = Nothing data ComponentDisabledReason = DisabledComponent | DisabledAllTests | DisabledAllBenchmarks + | DisabledAllButOne String diff --git a/Cabal/changelog b/Cabal/changelog index 1965a5fc597494225e960f636887ef38ce717e57..c4a01c2dc724b7629ff382780dcd5f965c2ed48b 100644 --- a/Cabal/changelog +++ b/Cabal/changelog @@ -66,6 +66,10 @@ internal use. * Macros in 'cabal_macros.h' are now ifndef'd, so that they don't cause an error if the macro is already defined. (#3041) + * './Setup configure' now accepts a single argument specifying + the component to be configured. The semantics of this mode + of operation are described in + <https://github.com/ghc-proposals/ghc-proposals/pull/4> 1.24.0.0 Ryan Thomas <ryan@ryant.org> March 2016 * Support GHC 8. diff --git a/Cabal/doc/installing-packages.markdown b/Cabal/doc/installing-packages.markdown index c95037f56d7047b8b4c4ffbbe468d7999e06165a..e1996429fe05d28e889bf18fff0d773b44995e28 100644 --- a/Cabal/doc/installing-packages.markdown +++ b/Cabal/doc/installing-packages.markdown @@ -410,6 +410,35 @@ is passed the `--with-hc-pkg`, `--prefix`, `--bindir`, `--libdir`, value of the `--with-compiler` option is passed in a `--with-hc` option and all options specified with `--configure-option=` are passed on. +In Cabal 2.0, support for a single positional argument was added to `setup configure` +This makes Cabal configure a the specific component to be +configured. Specified names can be qualified with `lib:` or +`exe:` in case just a name is ambiguous (as would be the case +for a package named `p` which has a library and an executable +named `p`.) This has the following effects: + +* Subsequent invocations of `build`, `register`, etc. operate only + on the configured component. + +* Cabal requires all "internal" dependencies (e.g., an executable + depending on a library defined in the same package) must be + found in the set of databases via `--package-db` (and related flags): + these dependencies are assumed to be up-to-date. A dependency can + be explicitly specified using `--dependency` simply by giving + the name of the internal library; e.g., the dependency for an + internal library named `foo` is given as `--dependency=pkg-internal=pkg-1.0-internal-abcd`. + +* Only the dependencies needed for the requested component are + required. Similarly, when `--exact-configuration` is specified, + it's only necessary to specify `--dependency` for the component. + (As mentioned previously, you *must* specify internal dependencies + as well.) + +* Internal `build-tools` dependencies are expected to be in the `PATH` + upon subsequent invocations of `setup`. + +Full details can be found in the [Componentized Cabal proposal](https://github.com/ezyang/ghc-proposals/blob/master/proposals/0000-componentized-cabal.rst). + ### Programs used for building ### The following options govern the programs used to process the source @@ -753,6 +782,19 @@ be controlled with the following command line options. To reset the stack, use `--package-db=clear`. +`--ipid=`_ipid_ +: Specifies the _installed package identifier_ of the package to be + built; this identifier is passed on to GHC and serves as the basis + for linker symbols and the `id` field in a `ghc-pkg` registration. + When a package has multiple components, the actual component + identifiers are derived off of this identifier (e.g., an + internal library `foo` from package `p-0.1-abcd` will get the + identifier `p-0.1-abcd-foo`. + +`--cid=`_cid_ +: Specifies the _component identifier_ of the component being built; + this is only valid if you are configuring a single component. + `--default-user-config=` _file_ : Allows a "default" `cabal.config` freeze file to be passed in manually. This file will only be used if one does not exist in the @@ -954,6 +996,18 @@ be controlled with the following command line options. for libraries it is also saved in the package registration information and used when compiling modules that use the library. +`--dependency`[=_pkgname_=_ipid_] +: Specify that a particular dependency should used for a particular + package name. In particular, it declares that any reference to + _pkgname_ in a `build-depends` should be resolved to _ipid_. + +`--exact-configuration` +: This changes Cabal to require every dependency be explicitly + specified using `--dependency`, rather than use Cabal's + (very simple) dependency solver. This is useful for programmatic + use of Cabal's API, where you want to error if you didn't + specify enough `--dependency` flags. + `--allow-newer`[=_pkgs_], `--allow-older`[=_pkgs_] : Selectively relax upper or lower bounds in dependencies without editing the package description respectively. diff --git a/Cabal/tests/PackageTests/ConfigureComponent/Exe/Bad.hs b/Cabal/tests/PackageTests/ConfigureComponent/Exe/Bad.hs new file mode 100644 index 0000000000000000000000000000000000000000..65ae4a05d5db90794a0f769fd667e23df74f67e2 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/Exe/Bad.hs @@ -0,0 +1,4 @@ +module Main where + +main :: IO () +main = putStrLn "Hello, Haskell!" diff --git a/Cabal/tests/PackageTests/ConfigureComponent/Exe/Exe.cabal b/Cabal/tests/PackageTests/ConfigureComponent/Exe/Exe.cabal new file mode 100644 index 0000000000000000000000000000000000000000..5c2822092fecc2995b9d60e246947b18b250a97b --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/Exe/Exe.cabal @@ -0,0 +1,18 @@ +name: Exe +version: 0.1.0.0 +license: BSD3 +author: Edward Z. Yang +maintainer: ezyang@cs.stanford.edu +build-type: Simple +cabal-version: >=1.10 + +executable goodexe + main-is: Good.hs + build-depends: base + default-language: Haskell2010 + +-- We deliberately don't configure badexe, so that we can build ONLY goodexe +executable badexe + main-is: Bad.hs + build-depends: totally-impossible-dependency-to-fill == 10000.25.6 + default-language: Haskell2010 diff --git a/Cabal/tests/PackageTests/ConfigureComponent/Exe/Good.hs b/Cabal/tests/PackageTests/ConfigureComponent/Exe/Good.hs new file mode 100644 index 0000000000000000000000000000000000000000..e8efe592d0c5e75acc4533577b3ac7964e3e0028 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/Exe/Good.hs @@ -0,0 +1,4 @@ +module Main where + +main :: IO () +main = putStrLn "OK" diff --git a/Cabal/tests/PackageTests/ConfigureComponent/SubLib/Lib.cabal b/Cabal/tests/PackageTests/ConfigureComponent/SubLib/Lib.cabal new file mode 100644 index 0000000000000000000000000000000000000000..85f5d879a9d36e457787cebb1e5989658c6083c0 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/SubLib/Lib.cabal @@ -0,0 +1,18 @@ +name: Lib +version: 0.1.0.0 +license: BSD3 +author: Edward Z. Yang +maintainer: ezyang@cs.stanford.edu +build-type: Simple +cabal-version: >=1.10 + +library sublib + build-depends: base + exposed-modules: Lib + default-language: Haskell2010 + +executable exe + main-is: Exe.hs + build-depends: base, sublib + hs-source-dirs: exe + default-language: Haskell2010 diff --git a/Cabal/tests/PackageTests/ConfigureComponent/SubLib/Lib.hs b/Cabal/tests/PackageTests/ConfigureComponent/SubLib/Lib.hs new file mode 100644 index 0000000000000000000000000000000000000000..1d7d07d5cbab05699f06f94e313077308167d235 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/SubLib/Lib.hs @@ -0,0 +1,2 @@ +module Lib where +lib = "OK" diff --git a/Cabal/tests/PackageTests/ConfigureComponent/SubLib/exe/Exe.hs b/Cabal/tests/PackageTests/ConfigureComponent/SubLib/exe/Exe.hs new file mode 100644 index 0000000000000000000000000000000000000000..6ee3fb933aad93f6d3fc7fef419efbaa2303f2f6 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/SubLib/exe/Exe.hs @@ -0,0 +1,2 @@ +import Lib +main = putStrLn lib diff --git a/Cabal/tests/PackageTests/ConfigureComponent/Test/Lib.hs b/Cabal/tests/PackageTests/ConfigureComponent/Test/Lib.hs new file mode 100644 index 0000000000000000000000000000000000000000..1d7d07d5cbab05699f06f94e313077308167d235 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/Test/Lib.hs @@ -0,0 +1,2 @@ +module Lib where +lib = "OK" diff --git a/Cabal/tests/PackageTests/ConfigureComponent/Test/Test.cabal b/Cabal/tests/PackageTests/ConfigureComponent/Test/Test.cabal new file mode 100644 index 0000000000000000000000000000000000000000..e1b1eca81824cf5b925ecab3163d77e5cbd93003 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/Test/Test.cabal @@ -0,0 +1,18 @@ +name: test-for-cabal +version: 0.1.0.0 +license: BSD3 +author: Edward Z. Yang +maintainer: ezyang@cs.stanford.edu +build-type: Simple +cabal-version: >=1.10 + +library + exposed-modules: Lib + build-depends: base + default-language: Haskell2010 + +test-suite testsuite + build-depends: test-for-cabal, testlib, base + type: exitcode-stdio-1.0 + main-is: Test.hs + hs-source-dirs: tests diff --git a/Cabal/tests/PackageTests/ConfigureComponent/Test/testlib/TestLib.hs b/Cabal/tests/PackageTests/ConfigureComponent/Test/testlib/TestLib.hs new file mode 100644 index 0000000000000000000000000000000000000000..d310486994431ef17493fde2d4cd95542a9f32d0 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/Test/testlib/TestLib.hs @@ -0,0 +1,3 @@ +module TestLib where +import Lib +testlib = lib diff --git a/Cabal/tests/PackageTests/ConfigureComponent/Test/testlib/testlib.cabal b/Cabal/tests/PackageTests/ConfigureComponent/Test/testlib/testlib.cabal new file mode 100644 index 0000000000000000000000000000000000000000..7ea7e7e3a8aad6495bb15b598a482f28fd33261c --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/Test/testlib/testlib.cabal @@ -0,0 +1,12 @@ +name: testlib +version: 0.1.0.0 +license: BSD3 +author: Edward Z. Yang +maintainer: ezyang@cs.stanford.edu +build-type: Simple +cabal-version: >=1.10 + +library + exposed-modules: TestLib + build-depends: test-for-cabal, base + default-language: Haskell2010 diff --git a/Cabal/tests/PackageTests/ConfigureComponent/Test/tests/Test.hs b/Cabal/tests/PackageTests/ConfigureComponent/Test/tests/Test.hs new file mode 100644 index 0000000000000000000000000000000000000000..63654821ba51d79ea40e0307e877ce794b40a2d3 --- /dev/null +++ b/Cabal/tests/PackageTests/ConfigureComponent/Test/tests/Test.hs @@ -0,0 +1,2 @@ +import TestLib +main = putStrLn testlib diff --git a/Cabal/tests/PackageTests/Tests.hs b/Cabal/tests/PackageTests/Tests.hs index 9ebe68fbfb3dc0638102d6608ab0b8223a3020d5..8cee8ce5dc66857869c686fe55f9c9a555c71419 100644 --- a/Cabal/tests/PackageTests/Tests.hs +++ b/Cabal/tests/PackageTests/Tests.hs @@ -439,6 +439,31 @@ tests config = do _ <- shell "autoreconf" ["-i"] cabal_build [] + tc "ConfigureComponent/Exe" $ do + withPackageDb $ do + cabal_install ["goodexe"] + runExe' "goodexe" [] >>= assertOutputContains "OK" + + tcs "ConfigureComponent/SubLib" "sublib-explicit" $ do + withPackageDb $ do + cabal_install ["sublib", "--cid", "sublib-0.1-abc"] + cabal_install ["exe", "--dependency", "sublib=sublib-0.1-abc"] + runExe' "exe" [] >>= assertOutputContains "OK" + + tcs "ConfigureComponent/SubLib" "sublib" $ do + withPackageDb $ do + cabal_install ["sublib"] + cabal_install ["exe"] + runExe' "exe" [] >>= assertOutputContains "OK" + + tcs "ConfigureComponent/Test" "test" $ do + withPackageDb $ do + cabal_install ["test-for-cabal"] + withPackage "testlib" $ cabal_install [] + cabal "configure" ["testsuite"] + cabal "build" [] + cabal "test" [] + -- Test that per-component copy works, when only building library tc "CopyComponent/Lib" $ withPackageDb $ do @@ -580,9 +605,9 @@ tests config = do uid = componentUnitId (targetCLBI target) dir = libdir (absoluteComponentInstallDirs pkg_descr lbi uid NoCopyDest) - assertBool "interface files should NOT be installed" . not + assertBool "interface files should be installed" =<< liftIO (doesFileExist (dir </> "Foo.hi")) - assertBool "static library should NOT be installed" . not + assertBool "static library should be installed" =<< liftIO (doesFileExist (dir </> mkLibName uid)) if is_dynamic then @@ -590,7 +615,7 @@ tests config = do =<< liftIO (doesFileExist (dir </> mkSharedLibName compiler_id uid)) else - assertBool "dynamic library should NOT be installed" . not + assertBool "dynamic library should be installed" =<< liftIO (doesFileExist (dir </> mkSharedLibName compiler_id uid)) shouldFail $ ghcPkg "describe" ["foo"] diff --git a/cabal-install/Distribution/Client/Config.hs b/cabal-install/Distribution/Client/Config.hs index 3b222f64a9b224b990adc15706ff44ce538c25d8..5545a7dedda895425eafb6d74c0a811cb437827c 100644 --- a/cabal-install/Distribution/Client/Config.hs +++ b/cabal-install/Distribution/Client/Config.hs @@ -302,6 +302,7 @@ instance Semigroup SavedConfig where -- TODO: NubListify configExtraIncludeDirs = lastNonEmpty configExtraIncludeDirs, configIPID = combine configIPID, + configCID = combine configCID, configDistPref = combine configDistPref, configCabalFilePath = combine configCabalFilePath, configVerbosity = combine configVerbosity, diff --git a/cabal-install/Distribution/Client/InstallPlan.hs b/cabal-install/Distribution/Client/InstallPlan.hs index ce1289e23ab42d36de66a4ed2cbef4e23324eedb..73132986cab01fd88a2833a3072ba6ca15665004 100644 --- a/cabal-install/Distribution/Client/InstallPlan.hs +++ b/cabal-install/Distribution/Client/InstallPlan.hs @@ -489,6 +489,7 @@ configureInstallPlan solverPlan = ConfiguredPackage { confPkgId = SimpleUnitId $ Configure.computeComponentId + Cabal.NoFlag Cabal.NoFlag (packageId spkg) PD.CLibName diff --git a/cabal-install/Distribution/Client/ProjectConfig/Legacy.hs b/cabal-install/Distribution/Client/ProjectConfig/Legacy.hs index 6fb99cb911ed9401fcd0bfcc863b766d3343a395..e5be5281613f61d55649479ffcc276a5807d7869 100644 --- a/cabal-install/Distribution/Client/ProjectConfig/Legacy.hs +++ b/cabal-install/Distribution/Client/ProjectConfig/Legacy.hs @@ -569,6 +569,7 @@ convertToLegacyAllPackageConfig configDependencies = mempty, configExtraIncludeDirs = mempty, configIPID = mempty, + configCID = mempty, configConfigurationsFlags = mempty, configTests = mempty, configCoverage = mempty, --TODO: don't merge @@ -633,6 +634,7 @@ convertToLegacyPerPackageConfig PackageConfig {..} = configDependencies = mempty, configExtraIncludeDirs = packageConfigExtraIncludeDirs, configIPID = mempty, + configCID = mempty, configConfigurationsFlags = packageConfigFlagAssignment, configTests = packageConfigTests, configCoverage = packageConfigCoverage, --TODO: don't merge diff --git a/cabal-install/Distribution/Client/ProjectPlanning.hs b/cabal-install/Distribution/Client/ProjectPlanning.hs index 0665c0bb93b2faefd980afd9e74fddd724a2d03f..704c88da992ba8e728d5b7dacfcd10f6fb680335 100644 --- a/cabal-install/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/Distribution/Client/ProjectPlanning.hs @@ -1941,6 +1941,7 @@ setupHsConfigureFlags (ReadyPackage configVerbosity = toFlag verbosity configIPID = toFlag (display (installedUnitId pkg)) + configCID = mempty configProgramPaths = Map.toList pkgProgramPaths configProgramArgs = Map.toList pkgProgramArgs