Skip to content

Commit

Permalink
DefaultBound definition and parsing
Browse files Browse the repository at this point in the history
  • Loading branch information
jasagredo committed Jan 17, 2024
1 parent 5803c1a commit c79b2b7
Show file tree
Hide file tree
Showing 15 changed files with 165 additions and 17 deletions.
18 changes: 17 additions & 1 deletion Cabal-described/src/Distribution/Described.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,7 @@ import Distribution.Types.AbiDependency (AbiDependency)
import Distribution.Types.AbiHash (AbiHash)
import Distribution.Types.BenchmarkType (BenchmarkType)
import Distribution.Types.BuildType (BuildType)
import Distribution.Types.DefaultBound (DefaultBound)
import Distribution.Types.Dependency (Dependency)
import Distribution.Types.ExecutableScope (ExecutableScope)
import Distribution.Types.ExeDependency (ExeDependency)
Expand Down Expand Up @@ -369,6 +370,21 @@ instance Described CompilerId where
<> fromString "-"
<> describe (Proxy :: Proxy Version)

instance Described DefaultBound where
describe _ = REUnion
[ REAppend
[ RENamed "pkg-name" (describe (Proxy :: Proxy PackageName))
, reChar ':' <> reUnqualComponent
, RESpaces <> vr
]
, REAppend
[ RENamed "pkg-name" (describe (Proxy :: Proxy PackageName))
, RESpaces <> vr
]
]
where
vr = RENamed "version-range" (describe (Proxy :: Proxy VersionRange))

instance Described Dependency where
describe _ = REAppend
[ RENamed "pkg-name" (describe (Proxy :: Proxy PackageName))
Expand Down Expand Up @@ -591,4 +607,4 @@ instance Described CompatLicenseFile where
describe _ = describe ([] :: [Token])

instance Described CompatFilePath where
describe _ = describe ([] :: [Token])
describe _ = describe ([] :: [Token])
1 change: 1 addition & 0 deletions Cabal-syntax/Cabal-syntax.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -133,6 +133,7 @@ library
Distribution.Types.CondTree
Distribution.Types.Condition
Distribution.Types.ConfVar
Distribution.Types.DefaultBound
Distribution.Types.Dependency
Distribution.Types.DependencyMap
Distribution.Types.ExeDependency
Expand Down
2 changes: 2 additions & 0 deletions Cabal-syntax/src/Distribution/Package.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ module Distribution.Package
, module Distribution.Types.PackageName
, module Distribution.Types.PkgconfigName
, module Distribution.Types.Dependency
, module Distribution.Types.DefaultBound
, Package (..)
, packageName
, packageVersion
Expand All @@ -44,6 +45,7 @@ import Distribution.Version

import Distribution.Types.AbiHash
import Distribution.Types.ComponentId
import Distribution.Types.DefaultBound
import Distribution.Types.Dependency
import Distribution.Types.Module
import Distribution.Types.MungedPackageId
Expand Down
2 changes: 2 additions & 0 deletions Cabal-syntax/src/Distribution/PackageDescription.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,7 @@ module Distribution.PackageDescription
, module Distribution.Types.PkgconfigVersionRange

-- * Dependencies
, module Distribution.Types.DefaultBound
, module Distribution.Types.Dependency
, module Distribution.Types.ExeDependency
, module Distribution.Types.LegacyExeDependency
Expand Down Expand Up @@ -95,6 +96,7 @@ import Distribution.Types.ComponentName
import Distribution.Types.CondTree
import Distribution.Types.Condition
import Distribution.Types.ConfVar
import Distribution.Types.DefaultBound
import Distribution.Types.Dependency
import Distribution.Types.ExeDependency
import Distribution.Types.Executable
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -104,7 +104,7 @@ packageDescriptionFieldGrammar
, c (List FSep (Identity (SymbolicPath PackageDir LicenseFile)) (SymbolicPath PackageDir LicenseFile))
, c (List FSep TestedWith (CompilerFlavor, VersionRange))
, c (List VCat FilePathNT String)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaFSep (Identity DefaultBound) DefaultBound)
, c FilePathNT
, c CompatLicenseFile
, c CompatFilePath
Expand Down Expand Up @@ -147,7 +147,7 @@ packageDescriptionFieldGrammar =
<*> monoidalFieldAla "extra-source-files" formatExtraSourceFiles L.extraSrcFiles
<*> monoidalFieldAla "extra-tmp-files" (alaList' VCat FilePathNT) L.extraTmpFiles
<*> monoidalFieldAla "extra-doc-files" (alaList' VCat FilePathNT) L.extraDocFiles
<*> monoidalFieldAla "default-package-bounds" formatDependencyList L.defaultPackageBounds
<*> monoidalFieldAla "default-package-bounds" (alaList CommaFSep) L.defaultPackageBounds
^^^ availableSince CabalSpecV3_12 []
where
packageIdentifierGrammar =
Expand Down Expand Up @@ -177,6 +177,7 @@ libraryFieldGrammar
, c (List CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity DefaultBound) DefaultBound)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List CommaVCat (Identity ModuleReexport) ModuleReexport)
, c (List FSep (MQuoted Extension) Extension)
Expand Down
70 changes: 70 additions & 0 deletions Cabal-syntax/src/Distribution/Types/DefaultBound.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,70 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Distribution.Types.DefaultBound where

import Distribution.Compat.Prelude

import Distribution.Types.Dependency
import Distribution.Types.ExeDependency
import Distribution.Types.PackageName
import Distribution.Types.PkgconfigDependency
import Distribution.Types.PkgconfigName
import Distribution.Types.PkgconfigVersionRange
import Distribution.Types.UnqualComponentName
import Distribution.Types.VersionRange

import Distribution.Parsec
import Distribution.Pretty

import qualified Distribution.Compat.CharParsing as P

-- | Describes a default bound on a package, executable or pkg-config package.
data DefaultBound
= DefaultUnqualBound PackageName VersionRange
| DefaultQualBound PackageName UnqualComponentName VersionRange
deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)

applyDefaultBoundToDependency :: Dependency -> DefaultBound -> Dependency
applyDefaultBoundToDependency dep@(Dependency pkg vorig l) (DefaultUnqualBound pkg' v)
| pkg == pkg' && isAnyVersion vorig = Dependency pkg v l
| otherwise = dep
applyDefaultBoundToDependency dep _ = dep

applyDefaultBoundToExeDependency :: ExeDependency -> DefaultBound -> ExeDependency
applyDefaultBoundToExeDependency dep@(ExeDependency pkg comp vorig) (DefaultQualBound pkg' comp' v)
| pkg == pkg' && comp == comp' && isAnyVersion vorig = ExeDependency pkg comp v
| otherwise = dep
applyDefaultBoundToExeDependency dep _ = dep

applyDefaultBoundToPkgconfigDependency :: PkgconfigDependency -> DefaultBound -> PkgconfigDependency
applyDefaultBoundToPkgconfigDependency dep@(PkgconfigDependency pkg PcAnyVersion) (DefaultUnqualBound pkg' v)
| pkg == mkPkgconfigName (unPackageName pkg') = PkgconfigDependency pkg (versionRangeToPkgconfigVersionRange v)
| otherwise = dep
applyDefaultBoundToPkgconfigDependency dep _ = dep

instance Binary DefaultBound
instance Structured DefaultBound
instance NFData DefaultBound where rnf = genericRnf

instance Pretty DefaultBound where
pretty (DefaultUnqualBound name ver) = pretty $ Dependency name ver mainLibSet
pretty (DefaultQualBound name comp ver) = pretty $ ExeDependency name comp ver

instance Parsec DefaultBound where
parsec = do
name <- parsec
mexe <-
( do
_ <- P.char ':'
exe <- lexemeParsec
pure (Just exe)
)
<|> pure Nothing
P.spaces
verRange <- parsec
case mexe of
Nothing ->
pure $ DefaultUnqualBound name verRange
Just exe ->
pure $ DefaultQualBound name exe verRange
3 changes: 2 additions & 1 deletion Cabal-syntax/src/Distribution/Types/PackageDescription.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,7 @@ import Distribution.Types.BuildType
import Distribution.Types.Component
import Distribution.Types.ComponentName
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.DefaultBound
import Distribution.Types.Dependency
import Distribution.Types.HookedBuildInfo
import Distribution.Types.PackageId
Expand Down Expand Up @@ -147,7 +148,7 @@ data PackageDescription = PackageDescription
, extraTmpFiles :: [FilePath]
, extraDocFiles :: [FilePath]
, -- default constraints to override unversioned dependencies
defaultPackageBounds :: [Dependency]
defaultPackageBounds :: [DefaultBound]
}
deriving (Generic, Show, Read, Eq, Ord, Typeable, Data)

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ import Distribution.Types.Benchmark.Lens (benchmarkBuildInfo, benchmarkName)
import Distribution.Types.BuildInfo (BuildInfo)
import Distribution.Types.BuildType (BuildType)
import Distribution.Types.ComponentName (ComponentName (..))
import Distribution.Types.Dependency (Dependency (..))
import Distribution.Types.DefaultBound (DefaultBound)
import Distribution.Types.Executable (Executable, exeModules)
import Distribution.Types.Executable.Lens (exeBuildInfo, exeName)
import Distribution.Types.ForeignLib (ForeignLib, foreignLibModules)
Expand Down Expand Up @@ -159,7 +159,7 @@ extraDocFiles :: Lens' PackageDescription [String]
extraDocFiles f s = fmap (\x -> s{T.extraDocFiles = x}) (f (T.extraDocFiles s))
{-# INLINE extraDocFiles #-}

defaultPackageBounds :: Lens' PackageDescription [Dependency]
defaultPackageBounds :: Lens' PackageDescription [DefaultBound]
defaultPackageBounds f s = fmap (\x -> s{T.defaultPackageBounds = x}) (f (T.defaultPackageBounds s))
{-# INLINE defaultPackageBounds #-}

Expand Down
1 change: 1 addition & 0 deletions Cabal-tests/tests/NoThunks.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,7 @@ instance NoThunks BuildType
instance NoThunks CabalSpecVersion
instance NoThunks CompilerFlavor
instance NoThunks ConfVar
instance NoThunks DefaultBound
instance NoThunks Dependency
instance NoThunks Executable
instance NoThunks ExecutableScope
Expand Down
8 changes: 4 additions & 4 deletions Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,15 +33,15 @@ md5Check proxy md5Int = structureHash proxy @?= md5FromInteger md5Int
md5CheckGenericPackageDescription :: Proxy GenericPackageDescription -> Assertion
md5CheckGenericPackageDescription proxy = md5Check proxy
#if MIN_VERSION_base(4,19,0)
0xc638caeb7531f107f64d12773f9430d0
0x7ce25ab876f3e4de03172716978209f1
#else
0x7a231bff7bb37049ec7f2ebfd98d3243
0x955db6c660ea7bf8dc6ec8526294cb64
#endif

md5CheckLocalBuildInfo :: Proxy LocalBuildInfo -> Assertion
md5CheckLocalBuildInfo proxy = md5Check proxy
#if MIN_VERSION_base(4,19,0)
0xceb2a9b9aa0555228a98bd875534be77
0xc816411c46295d3beb542601693cf371
#else
0xc94d93ef5dd99410a5b2f1f3c9853f00
0x6e1b8093172cddb2dba1a3ffa236e83d
#endif
1 change: 1 addition & 0 deletions Cabal-tree-diff/src/Data/TreeDiff/Instances/Cabal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,7 @@ instance ToExpr CompilerFlavor
instance ToExpr CompilerId
instance ToExpr ComponentId
instance ToExpr DebugInfoLevel
instance ToExpr DefaultBound
instance ToExpr DefUnitId
instance ToExpr DumpBuildInfo
instance ToExpr ExeDependency
Expand Down
13 changes: 11 additions & 2 deletions Cabal/src/Distribution/PackageDescription/Check.hs
Original file line number Diff line number Diff line change
Expand Up @@ -286,10 +286,11 @@ checkGenericPackageDescription
. pnPackageId
. ccNames
)

let ads =
maybe [] ((: []) . extractAssocDeps pName) condLibrary_
++ map (uncurry extractAssocDeps) condSubLibraries_
++ [Left (defaultPackageBounds packageDescription_)]
++ [Left $ defaultPackageBounds packageDescription_]

case condLibrary_ of
Just cl ->
Expand Down Expand Up @@ -519,7 +520,15 @@ checkPackageDescription
partitionDeps
[]
[mkUnqualComponentName "base"]
(mergeDependencies defaultPackageBounds_)
( mergeDependencies $
catMaybes $
map
( \x -> case x of
DefaultQualBound{} -> Nothing
DefaultUnqualBound p ver -> Just $ Dependency p ver mainLibSet
)
defaultPackageBounds_
)
let ick = const (PackageDistInexcusable BaseNoUpperBounds)
rck = PackageDistSuspiciousWarn . MissingUpperBounds CETDefaultPackageBounds
checkPVP ick ids
Expand Down
17 changes: 15 additions & 2 deletions Cabal/src/Distribution/PackageDescription/Check/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ checkCustomField (n, _) =

-- Either a list of dependencies coming from @package-constraints@ or a library
-- name / dependencies association list. Ultimately to be fed to PVP check.
type AssocDep = Either [Dependency] (UnqualComponentName, [Dependency])
type AssocDep = Either [DefaultBound] (UnqualComponentName, [Dependency])

-- Convenience function to partition important dependencies by name. To
-- be used together with checkPVP. Important: usually “base” or “Cabal”,
Expand All @@ -81,7 +81,20 @@ partitionDeps ads ns ds = do
-- the names of such targets
inNam = nub $ mapMaybe (either (const Nothing) (Just . fst)) fads :: [UnqualComponentName]
-- the dependencies of such targets
inDep = concatMap (either id snd) fads :: [Dependency]
inDep =
concatMap
( either
( catMaybes
. map
( \x -> case x of
DefaultUnqualBound name ver -> Just $ Dependency name ver mainLibSet
DefaultQualBound{} -> Nothing
)
)
snd
)
fads
:: [Dependency]

-- We exclude from checks:
-- 1. dependencies which are shared with main library / a
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -343,14 +343,14 @@ convCondTree flags dr pkg os arch cinfo pn fds comp getInfo solveExes@(SolveExec
, singleDep <- convLibDeps dr (alterDep dep) ] -- unconditional package dependencies
++ L.map (\e -> D.Simple (LDep dr (Ext e)) comp) (allExtensions bi) -- unconditional extension dependencies
++ L.map (\l -> D.Simple (LDep dr (Lang l)) comp) (allLanguages bi) -- unconditional language dependencies
++ L.map (\(PkgconfigDependency pkn vr) -> D.Simple (LDep dr (Pkg pkn vr)) comp) (pkgconfigDepends bi) -- unconditional pkg-config dependencies
++ L.map ((\(PkgconfigDependency pkn vr) -> D.Simple (LDep dr (Pkg pkn vr)) comp) . alterPkgconfigDep) (pkgconfigDepends bi) -- unconditional pkg-config dependencies
++ concatMap (convBranch flags dr pkg os arch cinfo pn fds comp getInfo solveExes) branches
-- build-tools dependencies
-- NB: Only include these dependencies if SolveExecutables
-- is True. It might be false in the legacy solver
-- codepath, in which case there won't be any record of
-- an executable we need.
++ [ D.Simple (convExeDep dr exeDep) comp
++ [ D.Simple (convExeDep dr (alterExeDep exeDep)) comp
| solveExes'
, exeDep <- getAllToolDependencies pkg bi
, not $ isInternal pkg exeDep
Expand All @@ -364,10 +364,32 @@ convCondTree flags dr pkg os arch cinfo pn fds comp getInfo solveExes@(SolveExec
if vorig == anyVersion
then
maybe x (\v -> Dependency name v ls) $
listToMaybe [ v2 | Dependency name2 v2 _ <- defaultPackageBounds pkg
listToMaybe [ v2 | DefaultUnqualBound name2 v2 <- defaultPackageBounds pkg
, name2 == name ]
else x

-- apply default-package-bounds field of pkg to the actual declared
-- exe dependencies
alterExeDep x@(ExeDependency name c vorig) =
if vorig == anyVersion
then
maybe x (\v -> ExeDependency name c v) $
listToMaybe [ v2 | DefaultQualBound name2 comp2 v2 <- defaultPackageBounds pkg
, name2 == name, c == comp2 ]
else x

-- apply default-package-bounds field of pkg to the actual declared
-- exe dependencies
alterPkgconfigDep x@(PkgconfigDependency name vorig) =
if vorig == PcAnyVersion
then
maybe x (\v -> PkgconfigDependency name v) $
listToMaybe [ versionRangeToPkgconfigVersionRange v2
| DefaultUnqualBound name2 v2 <- defaultPackageBounds pkg
, mkPkgconfigName (unPackageName name2) == name ]
else x


data SimpleFlaggedDepKey qpn =
SimpleFlaggedDepKey (PkgComponent qpn) Component
deriving (Eq, Ord)
Expand Down
9 changes: 9 additions & 0 deletions doc/buildinfo-fields-reference.rst
Original file line number Diff line number Diff line change
Expand Up @@ -568,6 +568,15 @@ data-files
.. math::
\mathrm{commalist}\left\{ \mathop{\mathit{hs\text{-}string}}\mid{{[\mathop{\mathord{``}\mathtt{\ }\mathord{"}}\mathop{\mathord{``}\mathtt{\text{,}}\mathord{"}}]^c}}^+_{} \right\}
default-package-bounds
* Monoidal field
* Available since ``cabal-version: 3.12``.
* Documentation of :pkg-field:`default-package-bounds`

.. math::
\mathrm{commalist}\left\{ \mathop{\mathit{pkg\text{-}name}}\mathop{\mathord{``}\mathtt{\text{:}}\mathord{"}}\mathop{\mathit{unqual\text{-}name}}\circ\mathop{\mathit{version\text{-}range}}\mid\mathop{\mathit{pkg\text{-}name}}\circ\mathop{\mathit{version\text{-}range}} \right\}
description
* Free text field
* Documentation of :pkg-field:`description`
Expand Down

0 comments on commit c79b2b7

Please sign in to comment.