diff --git a/Cabal/Cabal-quickcheck/src/Test/QuickCheck/Instances/Cabal.hs b/Cabal/Cabal-quickcheck/src/Test/QuickCheck/Instances/Cabal.hs index 942cd8d085893f35d5f71f1c6609d19823e46b42..0c3d9affd2ce02e35beee6a9ce15548a59b87bff 100644 --- a/Cabal/Cabal-quickcheck/src/Test/QuickCheck/Instances/Cabal.hs +++ b/Cabal/Cabal-quickcheck/src/Test/QuickCheck/Instances/Cabal.hs @@ -63,6 +63,7 @@ instance Arbitrary Version where ,(1, return 0xfffd) ,(1, return 0xfffe) -- max fitting into packed W64 ,(1, return 0xffff) + ,(1, return 999999998) ,(1, return 999999999) ,(1, return 0x10000)] return (mkVersion branch) @@ -84,7 +85,7 @@ instance Arbitrary VersionRange where , (1, fmap earlierVersion arbitrary) , (1, fmap orEarlierVersion arbitrary) , (1, fmap orEarlierVersion' arbitrary) - , (1, fmap withinVersion arbitrary) + , (1, fmap withinVersion arbitraryV) , (1, fmap majorBoundVersion arbitrary) ] ++ if n == 0 then [] else [ (2, liftA2 unionVersionRanges verRangeExp2 verRangeExp2) @@ -93,18 +94,19 @@ instance Arbitrary VersionRange where where verRangeExp2 = verRangeExp (n `div` 2) + arbitraryV :: Gen Version + arbitraryV = arbitrary `suchThat` \v -> all (< 999999999) (versionNumbers v) + orLaterVersion' v = unionVersionRanges (LaterVersion v) (ThisVersion v) orEarlierVersion' v = unionVersionRanges (EarlierVersion v) (ThisVersion v) - shrink AnyVersion = [] shrink (ThisVersion v) = map ThisVersion (shrink v) shrink (LaterVersion v) = map LaterVersion (shrink v) shrink (EarlierVersion v) = map EarlierVersion (shrink v) shrink (OrLaterVersion v) = LaterVersion v : map OrLaterVersion (shrink v) shrink (OrEarlierVersion v) = EarlierVersion v : map OrEarlierVersion (shrink v) - shrink (WildcardVersion v) = map WildcardVersion ( shrink v) shrink (MajorBoundVersion v) = map MajorBoundVersion (shrink v) shrink (UnionVersionRanges a b) = a : b : map (uncurry UnionVersionRanges) (shrink (a, b)) shrink (IntersectVersionRanges a b) = a : b : map (uncurry IntersectVersionRanges) (shrink (a, b)) diff --git a/Cabal/Distribution/Types/Dependency.hs b/Cabal/Distribution/Types/Dependency.hs index a16f5f7f0a18475293299a0892e4f757f71134ff..638186a9d48118e31cebe3cce761a5b524b26b15 100644 --- a/Cabal/Distribution/Types/Dependency.hs +++ b/Cabal/Distribution/Types/Dependency.hs @@ -15,7 +15,8 @@ import Distribution.Compat.Prelude import Prelude () import Distribution.Version - (VersionRange, anyVersion, notThisVersion, simplifyVersionRange, thisVersion) + (VersionRange, anyVersion,notThisVersion, simplifyVersionRange, thisVersion) +import Distribution.Types.VersionRange (isAnyVersionLight) import Distribution.CabalSpecVersion import Distribution.Compat.CharParsing (char, spaces) @@ -76,8 +77,12 @@ instance Structured Dependency instance NFData Dependency where rnf = genericRnf instance Pretty Dependency where - pretty (Dependency name ver sublibs) = withSubLibs (pretty name) <+> pretty ver + pretty (Dependency name ver sublibs) = withSubLibs (pretty name) <+> pver where + -- TODO: change to isAnyVersion after #6736 + pver | isAnyVersionLight ver = PP.empty + | otherwise = pretty ver + withSubLibs doc | sublibs == mainLib = doc | otherwise = doc <<>> PP.colon <<>> PP.braces prettySublibs @@ -90,13 +95,13 @@ instance Pretty Dependency where -- | -- -- >>> simpleParsec "mylib:sub" :: Maybe Dependency --- Just (Dependency (PackageName "mylib") AnyVersion (fromList [LSubLibName (UnqualComponentName "sub")])) +-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromList [LSubLibName (UnqualComponentName "sub")])) -- -- >>> simpleParsec "mylib:{sub1,sub2}" :: Maybe Dependency --- Just (Dependency (PackageName "mylib") AnyVersion (fromList [LSubLibName (UnqualComponentName "sub1"),LSubLibName (UnqualComponentName "sub2")])) +-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromList [LSubLibName (UnqualComponentName "sub1"),LSubLibName (UnqualComponentName "sub2")])) -- -- >>> simpleParsec "mylib:{ sub1 , sub2 }" :: Maybe Dependency --- Just (Dependency (PackageName "mylib") AnyVersion (fromList [LSubLibName (UnqualComponentName "sub1"),LSubLibName (UnqualComponentName "sub2")])) +-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromList [LSubLibName (UnqualComponentName "sub1"),LSubLibName (UnqualComponentName "sub2")])) -- -- >>> simpleParsec "mylib:{ sub1 , sub2 } ^>= 42" :: Maybe Dependency -- Just (Dependency (PackageName "mylib") (MajorBoundVersion (mkVersion [42])) (fromList [LSubLibName (UnqualComponentName "sub1"),LSubLibName (UnqualComponentName "sub2")])) @@ -105,9 +110,9 @@ instance Pretty Dependency where -- Just (Dependency (PackageName "mylib") (MajorBoundVersion (mkVersion [42])) (fromList [])) -- -- >>> traverse_ print (map simpleParsec ["mylib:mylib", "mylib:{mylib}", "mylib:{mylib,sublib}" ] :: [Maybe Dependency]) --- Just (Dependency (PackageName "mylib") AnyVersion (fromList [LMainLibName])) --- Just (Dependency (PackageName "mylib") AnyVersion (fromList [LMainLibName])) --- Just (Dependency (PackageName "mylib") AnyVersion (fromList [LMainLibName,LSubLibName (UnqualComponentName "sublib")])) +-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromList [LMainLibName])) +-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromList [LMainLibName])) +-- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromList [LMainLibName,LSubLibName (UnqualComponentName "sublib")])) -- -- Spaces around colon are not allowed: -- @@ -117,7 +122,7 @@ instance Pretty Dependency where -- Sublibrary syntax is accepted since @cabal-version: 3.0@ -- -- >>> map (`simpleParsec'` "mylib:sub") [CabalSpecV2_4, CabalSpecV3_0] :: [Maybe Dependency] --- [Nothing,Just (Dependency (PackageName "mylib") AnyVersion (fromList [LSubLibName (UnqualComponentName "sub")]))] +-- [Nothing,Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromList [LSubLibName (UnqualComponentName "sub")]))] -- instance Parsec Dependency where parsec = do @@ -157,7 +162,7 @@ mainLib = Set.singleton LMainLibName instance Described Dependency where describe _ = REAppend [ RENamed "pkg-name" (describe (Proxy :: Proxy PackageName)) - , REOpt $ + , REOpt $ reChar ':' <> REUnion [ reUnqualComponent @@ -168,7 +173,7 @@ instance Described Dependency where , REMunch reSpacedComma reUnqualComponent , RESpaces , reChar '}' - ] + ] ] -- TODO: RESpaces1 should be just RESpaces, but we are able -- to generate non-parseable strings without mandatory space diff --git a/Cabal/Distribution/Types/ExeDependency.hs b/Cabal/Distribution/Types/ExeDependency.hs index ea8040aa6508c216d5522d97d579651cf2efa7e7..8d283be72c6eeb8a1adcc5ea0c59cc9b5b05ca0a 100644 --- a/Cabal/Distribution/Types/ExeDependency.hs +++ b/Cabal/Distribution/Types/ExeDependency.hs @@ -14,10 +14,10 @@ import Distribution.Pretty import Distribution.Types.ComponentName import Distribution.Types.PackageName import Distribution.Types.UnqualComponentName -import Distribution.Version (VersionRange, anyVersion) +import Distribution.Version (VersionRange, anyVersion, isAnyVersion) import qualified Distribution.Compat.CharParsing as P -import Text.PrettyPrint (text, (<+>)) +import qualified Text.PrettyPrint as PP -- | Describes a dependency on an executable from a package -- @@ -33,14 +33,17 @@ instance NFData ExeDependency where rnf = genericRnf instance Pretty ExeDependency where pretty (ExeDependency name exe ver) = - (pretty name <<>> text ":" <<>> pretty exe) <+> pretty ver + pretty name <<>> PP.colon <<>> pretty exe PP.<+> pver + where + pver | isAnyVersion ver = PP.empty + | otherwise = pretty ver -- | -- -- Examples -- -- >>> simpleParsec "happy:happy" :: Maybe ExeDependency --- Just (ExeDependency (PackageName "happy") (UnqualComponentName "happy") AnyVersion) +-- Just (ExeDependency (PackageName "happy") (UnqualComponentName "happy") (OrLaterVersion (mkVersion [0]))) -- -- >>> simpleParsec "happy:happy >= 1.19.12" :: Maybe ExeDependency -- Just (ExeDependency (PackageName "happy") (UnqualComponentName "happy") (OrLaterVersion (mkVersion [1,19,12]))) diff --git a/Cabal/Distribution/Types/PkgconfigDependency.hs b/Cabal/Distribution/Types/PkgconfigDependency.hs index f55eac84d6a3e444af84410f6fc2f8de4cbe0aa9..690da56ac471848033972f4e6ee75794edeedac8 100644 --- a/Cabal/Distribution/Types/PkgconfigDependency.hs +++ b/Cabal/Distribution/Types/PkgconfigDependency.hs @@ -30,8 +30,8 @@ instance Structured PkgconfigDependency instance NFData PkgconfigDependency where rnf = genericRnf instance Pretty PkgconfigDependency where - pretty (PkgconfigDependency name ver) = - pretty name <+> pretty ver + pretty (PkgconfigDependency name PcAnyVersion) = pretty name + pretty (PkgconfigDependency name ver) = pretty name <+> pretty ver instance Parsec PkgconfigDependency where parsec = do diff --git a/Cabal/Distribution/Types/PkgconfigVersionRange.hs b/Cabal/Distribution/Types/PkgconfigVersionRange.hs index 177a57c9171bca83320aa472df731faa895c9199..6c13c47953b0d6c549880f7c72061b3dfc7b000a 100644 --- a/Cabal/Distribution/Types/PkgconfigVersionRange.hs +++ b/Cabal/Distribution/Types/PkgconfigVersionRange.hs @@ -18,6 +18,7 @@ import Distribution.Parsec import Distribution.Pretty import Distribution.Types.PkgconfigVersion import Distribution.Types.Version +import Distribution.Types.VersionInterval import Distribution.Types.VersionRange import qualified Data.ByteString.Char8 as BS8 @@ -142,10 +143,19 @@ versionToPkgconfigVersion :: Version -> PkgconfigVersion versionToPkgconfigVersion = PkgconfigVersion . BS8.pack . prettyShow versionRangeToPkgconfigVersionRange :: VersionRange -> PkgconfigVersionRange -versionRangeToPkgconfigVersionRange = foldVersionRange - anyPkgconfigVersion - (PcThisVersion . versionToPkgconfigVersion) - (PcLaterVersion . versionToPkgconfigVersion) - (PcEarlierVersion . versionToPkgconfigVersion) - PcUnionVersionRanges - PcIntersectVersionRanges +versionRangeToPkgconfigVersionRange vr + | isAnyVersion vr + = PcAnyVersion + | otherwise + = case asVersionIntervals vr of + [] -> PcEarlierVersion (PkgconfigVersion (BS8.pack "0")) + (i:is) -> foldl (\r j -> PcUnionVersionRanges r (conv j)) (conv i) is + where + conv (LowerBound v b, NoUpperBound) = convL v b + conv (LowerBound v b, UpperBound u c) = PcIntersectVersionRanges (convL v b) (convU u c) + + convL v ExclusiveBound = PcLaterVersion (versionToPkgconfigVersion v) + convL v InclusiveBound = PcOrLaterVersion (versionToPkgconfigVersion v) + + convU v ExclusiveBound = PcEarlierVersion (versionToPkgconfigVersion v) + convU v InclusiveBound = PcOrEarlierVersion (versionToPkgconfigVersion v) diff --git a/Cabal/Distribution/Types/VersionInterval.hs b/Cabal/Distribution/Types/VersionInterval.hs index ebb2178fc53c3b0ef0adecc1ad76cbce1ea0894e..05354105d24e859427cde2cd25cb46ceb61ba1d4 100644 --- a/Cabal/Distribution/Types/VersionInterval.hs +++ b/Cabal/Distribution/Types/VersionInterval.hs @@ -26,7 +26,7 @@ import Distribution.Compat.Prelude import Control.Exception (assert) import Distribution.Types.Version -import Distribution.Types.VersionRange +import Distribution.Types.VersionRange.Internal -- NonEmpty import qualified Prelude (foldr1) @@ -200,15 +200,18 @@ withinIntervals v (VersionIntervals intervals) = any withinInterval intervals -- | Convert a 'VersionRange' to a sequence of version intervals. -- toVersionIntervals :: VersionRange -> VersionIntervals -toVersionIntervals = foldVersionRange - ( chkIvl (minLowerBound, NoUpperBound)) - (\v -> chkIvl (LowerBound v InclusiveBound, UpperBound v InclusiveBound)) - (\v -> chkIvl (LowerBound v ExclusiveBound, NoUpperBound)) - (\v -> if isVersion0 v then VersionIntervals [] else - chkIvl (minLowerBound, UpperBound v ExclusiveBound)) - unionVersionIntervals - intersectVersionIntervals - where +toVersionIntervals = cataVersionRange alg where + alg (ThisVersionF v) = chkIvl (LowerBound v InclusiveBound, UpperBound v InclusiveBound) + alg (LaterVersionF v) = chkIvl (LowerBound v ExclusiveBound, NoUpperBound) + alg (OrLaterVersionF v) = chkIvl (LowerBound v InclusiveBound, NoUpperBound) + alg (EarlierVersionF v) + | isVersion0 v = VersionIntervals [] + | otherwise = chkIvl (minLowerBound, UpperBound v ExclusiveBound) + alg (OrEarlierVersionF v) = chkIvl (minLowerBound, UpperBound v InclusiveBound) + alg (MajorBoundVersionF v) = chkIvl (LowerBound v InclusiveBound, UpperBound (majorUpperBound v) ExclusiveBound) + alg (UnionVersionRangesF v1 v2) = unionVersionIntervals v1 v2 + alg (IntersectVersionRangesF v1 v2) = intersectVersionIntervals v1 v2 + chkIvl interval = checkInvariant (VersionIntervals [interval]) -- | Convert a 'VersionIntervals' value back into a 'VersionRange' expression @@ -223,9 +226,6 @@ fromVersionIntervals (VersionIntervals intervals) = interval (LowerBound v InclusiveBound) (UpperBound v' InclusiveBound) | v == v' = thisVersion v - interval (LowerBound v InclusiveBound) - (UpperBound v' ExclusiveBound) | isWildcardRange v v' - = withinVersion v interval l u = lowerBound l `intersectVersionRanges'` upperBound u lowerBound (LowerBound v InclusiveBound) diff --git a/Cabal/Distribution/Types/VersionRange.hs b/Cabal/Distribution/Types/VersionRange.hs index 7ef2286ca2c6e334becd314ebb5977080358a184..2bd8a8f9416366e66590390d5be95c46f5286c8e 100644 --- a/Cabal/Distribution/Types/VersionRange.hs +++ b/Cabal/Distribution/Types/VersionRange.hs @@ -30,6 +30,8 @@ module Distribution.Types.VersionRange ( embedVersionRange, -- ** Utilities + isAnyVersion, + isAnyVersionLight, wildcardUpperBound, majorUpperBound, isWildcardRange, @@ -38,8 +40,8 @@ module Distribution.Types.VersionRange ( import Distribution.Compat.Prelude import Distribution.Types.Version +import Distribution.Types.VersionInterval import Distribution.Types.VersionRange.Internal -import Distribution.Utils.Generic import Prelude () -- | Fold over the basic syntactic structure of a 'VersionRange'. @@ -57,25 +59,19 @@ foldVersionRange :: a -- ^ @\"-any\"@ version -> (a -> a -> a) -- ^ @\"_ || _\"@ union -> (a -> a -> a) -- ^ @\"_ && _\"@ intersection -> VersionRange -> a -foldVersionRange anyv this later earlier union intersect = fold +foldVersionRange _any this later earlier union intersect = fold where fold = cataVersionRange alg - alg AnyVersionF = anyv alg (ThisVersionF v) = this v alg (LaterVersionF v) = later v alg (OrLaterVersionF v) = union (this v) (later v) alg (EarlierVersionF v) = earlier v alg (OrEarlierVersionF v) = union (this v) (earlier v) - alg (WildcardVersionF v) = fold (wildcard v) alg (MajorBoundVersionF v) = fold (majorBound v) alg (UnionVersionRangesF v1 v2) = union v1 v2 alg (IntersectVersionRangesF v1 v2) = intersect v1 v2 - wildcard v = intersectVersionRanges - (orLaterVersion v) - (earlierVersion (wildcardUpperBound v)) - majorBound v = intersectVersionRanges (orLaterVersion v) (earlierVersion (majorUpperBound v)) @@ -122,16 +118,35 @@ withinRange v = foldVersionRange (||) (&&) +-- | Does this 'VersionRange' place any restriction on the 'Version' or is it +-- in fact equivalent to 'AnyVersion'. +-- +-- Note this is a semantic check, not simply a syntactic check. So for example +-- the following is @True@ (for all @v@). +-- +-- > isAnyVersion (EarlierVersion v `UnionVersionRanges` orLaterVersion v) +-- +isAnyVersion :: VersionRange -> Bool +isAnyVersion vr = case asVersionIntervals vr of + [(LowerBound v InclusiveBound, NoUpperBound)] -> v == version0 + _ -> False + +-- A fast and non-precise version of 'isAnyVersion', +-- returns 'True' only for @>= 0@ 'VersionRange's. +-- +-- /Do not use/. The "VersionIntervals don't destroy MajorBoundVersion" +-- https://github.com/haskell/cabal/pull/6736 pull-request +-- will change 'simplifyVersionRange' to properly preserve semantics. +-- Then we can use it to normalise 'VersionRange's in tests. +-- +isAnyVersionLight :: VersionRange -> Bool +isAnyVersionLight (OrLaterVersion v) = v == version0 +isAnyVersionLight _vr = False + ---------------------------- -- Wildcard range utilities -- --- | @since 2.2 -wildcardUpperBound :: Version -> Version -wildcardUpperBound = alterVersion $ - \lowerBound -> case unsnoc lowerBound of - Nothing -> [] - Just (xs, x) -> xs ++ [x + 1] isWildcardRange :: Version -> Version -> Bool isWildcardRange ver1 ver2 = check (versionNumbers ver1) (versionNumbers ver2) diff --git a/Cabal/Distribution/Types/VersionRange/Internal.hs b/Cabal/Distribution/Types/VersionRange/Internal.hs index 43e67c567baebc4d93a2cec5a4f5020b49edf9f6..dfd71b711934b9bf3ec72836135d7e9d8ceeeb9b 100644 --- a/Cabal/Distribution/Types/VersionRange/Internal.hs +++ b/Cabal/Distribution/Types/VersionRange/Internal.hs @@ -31,6 +31,7 @@ module Distribution.Types.VersionRange.Internal , versionRangeParser , majorUpperBound + , wildcardUpperBound ) where import Distribution.Compat.Prelude @@ -41,6 +42,7 @@ import Distribution.CabalSpecVersion import Distribution.FieldGrammar.Described import Distribution.Parsec import Distribution.Pretty +import Distribution.Utils.Generic (unsnoc) import Text.PrettyPrint ((<+>)) import qualified Distribution.Compat.CharParsing as P @@ -48,13 +50,11 @@ import qualified Distribution.Compat.DList as DList import qualified Text.PrettyPrint as Disp data VersionRange - = AnyVersion - | ThisVersion Version -- = version + = ThisVersion Version -- = version | LaterVersion Version -- > version (NB. not >=) | OrLaterVersion Version -- >= version | EarlierVersion Version -- < version | OrEarlierVersion Version -- <= version - | WildcardVersion Version -- == ver.* (same as >= ver && < ver+1) | MajorBoundVersion Version -- @^>= ver@ (same as >= ver && < MAJ(ver)+1) | UnionVersionRanges VersionRange VersionRange | IntersectVersionRanges VersionRange VersionRange @@ -70,18 +70,17 @@ instance NFData VersionRange where rnf = genericRnf -- > withinRange v anyVersion = True -- anyVersion :: VersionRange -anyVersion = AnyVersion +anyVersion = OrLaterVersion (mkVersion [0]) -- | The empty version range, that is a version range containing no versions. -- -- This can be constructed using any unsatisfiable version range expression, --- for example @> 1 && < 1@. +-- for example @< 0@. -- -- > withinRange v noVersion = False -- noVersion :: VersionRange -noVersion = IntersectVersionRanges (LaterVersion v) (EarlierVersion v) - where v = mkVersion [1] +noVersion = EarlierVersion (mkVersion [0]) -- | The version range @== v@ -- @@ -151,7 +150,9 @@ intersectVersionRanges = IntersectVersionRanges -- > upper (Version lower t) = Version (init lower ++ [last lower + 1]) t -- withinVersion :: Version -> VersionRange -withinVersion = WildcardVersion +withinVersion v = intersectVersionRanges + (orLaterVersion v) + (earlierVersion (wildcardUpperBound v)) -- | The version range @^>= v@. -- @@ -169,13 +170,11 @@ majorBoundVersion = MajorBoundVersion -- -- @since 2.2 data VersionRangeF a - = AnyVersionF - | ThisVersionF Version -- = version + = ThisVersionF Version -- = version | LaterVersionF Version -- > version (NB. not >=) | OrLaterVersionF Version -- >= version | EarlierVersionF Version -- < version | OrEarlierVersionF Version -- <= version - | WildcardVersionF Version -- == ver.* (same as >= ver && < ver+1) | MajorBoundVersionF Version -- @^>= ver@ (same as >= ver && < MAJ(ver)+1) | UnionVersionRangesF a a | IntersectVersionRangesF a a @@ -184,13 +183,11 @@ data VersionRangeF a -- | @since 2.2 projectVersionRange :: VersionRange -> VersionRangeF VersionRange -projectVersionRange AnyVersion = AnyVersionF projectVersionRange (ThisVersion v) = ThisVersionF v projectVersionRange (LaterVersion v) = LaterVersionF v projectVersionRange (OrLaterVersion v) = OrLaterVersionF v projectVersionRange (EarlierVersion v) = EarlierVersionF v projectVersionRange (OrEarlierVersion v) = OrEarlierVersionF v -projectVersionRange (WildcardVersion v) = WildcardVersionF v projectVersionRange (MajorBoundVersion v) = MajorBoundVersionF v projectVersionRange (UnionVersionRanges a b) = UnionVersionRangesF a b projectVersionRange (IntersectVersionRanges a b) = IntersectVersionRangesF a b @@ -203,13 +200,11 @@ cataVersionRange f = c where c = f . fmap c . projectVersionRange -- | @since 2.2 embedVersionRange :: VersionRangeF VersionRange -> VersionRange -embedVersionRange AnyVersionF = AnyVersion embedVersionRange (ThisVersionF v) = ThisVersion v embedVersionRange (LaterVersionF v) = LaterVersion v embedVersionRange (OrLaterVersionF v) = OrLaterVersion v embedVersionRange (EarlierVersionF v) = EarlierVersion v embedVersionRange (OrEarlierVersionF v) = OrEarlierVersion v -embedVersionRange (WildcardVersionF v) = WildcardVersion v embedVersionRange (MajorBoundVersionF v) = MajorBoundVersion v embedVersionRange (UnionVersionRangesF a b) = UnionVersionRanges a b embedVersionRange (IntersectVersionRangesF a b) = IntersectVersionRanges a b @@ -232,31 +227,59 @@ hyloVersionRange f g = h where h = f . fmap h . g -- Parsec & Pretty ------------------------------------------------------------------------------- +-- | +-- +-- >>> fmap pretty (simpleParsec' CabalSpecV1_6 "== 3.2.*" :: Maybe VersionRange) +-- Just >=3.2 && <3.3 +-- +-- >>> fmap (prettyVersioned CabalSpecV1_6) (simpleParsec' CabalSpecV1_6 "== 3.2.*" :: Maybe VersionRange) +-- Just ==3.2.* +-- +-- >>> fmap pretty (simpleParsec' CabalSpecV1_6 "-any" :: Maybe VersionRange) +-- Just >=0 +-- +-- >>> fmap (prettyVersioned CabalSpecV1_6) (simpleParsec' CabalSpecV1_6 "-any" :: Maybe VersionRange) +-- Just >=0 +-- instance Pretty VersionRange where - pretty = fst . cataVersionRange alg - where - alg AnyVersionF = (Disp.text "-any", 0 :: Int) - alg (ThisVersionF v) = (Disp.text "==" <<>> pretty v, 0) - alg (LaterVersionF v) = (Disp.char '>' <<>> pretty v, 0) - alg (OrLaterVersionF v) = (Disp.text ">=" <<>> pretty v, 0) - alg (EarlierVersionF v) = (Disp.char '<' <<>> pretty v, 0) - alg (OrEarlierVersionF v) = (Disp.text "<=" <<>> pretty v, 0) - alg (WildcardVersionF v) = (Disp.text "==" <<>> dispWild v, 0) - alg (MajorBoundVersionF v) = (Disp.text "^>=" <<>> pretty v, 0) - alg (UnionVersionRangesF (r1, p1) (r2, p2)) = - (punct 1 p1 r1 <+> Disp.text "||" <+> punct 2 p2 r2 , 2) - alg (IntersectVersionRangesF (r1, p1) (r2, p2)) = - (punct 0 p1 r1 <+> Disp.text "&&" <+> punct 1 p2 r2 , 1) - - dispWild ver = - Disp.hcat (Disp.punctuate (Disp.char '.') - (map Disp.int $ versionNumbers ver)) - <<>> Disp.text ".*" - - punct p p' | p < p' = Disp.parens - | otherwise = id - --- | + pretty = prettyVersioned cabalSpecLatest + + prettyVersioned csv + | csv > CabalSpecV1_6 = prettyVersionRange + | otherwise = prettyVersionRange16 + +prettyVersionRange :: VersionRange -> Disp.Doc +prettyVersionRange = fst . cataVersionRange alg + where + alg :: VersionRangeF (Disp.Doc, Int) -> (Disp.Doc, Int) + alg (ThisVersionF v) = (Disp.text "==" <<>> pretty v, 0) + alg (LaterVersionF v) = (Disp.char '>' <<>> pretty v, 0) + alg (OrLaterVersionF v) = (Disp.text ">=" <<>> pretty v, 0) + alg (EarlierVersionF v) = (Disp.char '<' <<>> pretty v, 0) + alg (OrEarlierVersionF v) = (Disp.text "<=" <<>> pretty v, 0) + alg (MajorBoundVersionF v) = (Disp.text "^>=" <<>> pretty v, 0) + alg (UnionVersionRangesF (r1, p1) (r2, p2)) = + (punct 1 p1 r1 <+> Disp.text "||" <+> punct 2 p2 r2 , 2) + alg (IntersectVersionRangesF (r1, p1) (r2, p2)) = + (punct 0 p1 r1 <+> Disp.text "&&" <+> punct 1 p2 r2 , 1) + + punct p p' | p < p' = Disp.parens + | otherwise = id + +-- | Don't use && and || operators. If possible. +prettyVersionRange16 :: VersionRange -> Disp.Doc +prettyVersionRange16 (IntersectVersionRanges (OrLaterVersion v) (EarlierVersion u)) + | u == wildcardUpperBound v + = Disp.text "==" <<>> dispWild v + where + dispWild ver = + Disp.hcat (Disp.punctuate (Disp.char '.') + (map Disp.int $ versionNumbers ver)) + <<>> Disp.text ".*" + +prettyVersionRange16 vr = prettyVersionRange vr + +-- | -- -- >>> simpleParsec "^>= 3.4" :: Maybe VersionRange -- Just (MajorBoundVersion (mkVersion [3,4])) @@ -276,7 +299,7 @@ instance Pretty VersionRange where -- @-none@ is introduced in 1.22 -- -- >>> map (`simpleParsec'` "-none") [CabalSpecV1_20, CabalSpecV1_22] :: [Maybe VersionRange] --- [Nothing,Just (IntersectVersionRanges (LaterVersion (mkVersion [1])) (EarlierVersion (mkVersion [1])))] +-- [Nothing,Just (EarlierVersion (mkVersion [0]))] -- -- Operators are introduced in 1.8. Issues only a warning. -- @@ -286,7 +309,7 @@ instance Pretty VersionRange where -- Wild-version ranges are introduced in 1.6. Issues only a warning. -- -- >>> map (`simpleParsecW'` "== 1.2.*") [CabalSpecV1_4, CabalSpecV1_6] :: [Maybe VersionRange] --- [Nothing,Just (WildcardVersion (mkVersion [1,2]))] +-- [Nothing,Just (IntersectVersionRanges (OrLaterVersion (mkVersion [1,2])) (EarlierVersion (mkVersion [1,3])))] -- instance Parsec VersionRange where parsec = askCabalSpecVersion >>= versionRangeParser versionDigitParser @@ -302,13 +325,13 @@ instance Described VersionRange where , ">=" <> RESpaces <> ver , "^>=" <> RESpaces <> ver - , reVar0 <> RESpaces <> "||" <> RESpaces <> reVar0 - , reVar0 <> RESpaces <> "&&" <> RESpaces <> reVar0 - , "(" <> RESpaces <> reVar0 <> RESpaces <> ")" - -- ==0.1.* , "==" <> RESpaces <> wildVer + , reVar0 <> RESpaces <> "||" <> RESpaces <> reVar0 + , reVar0 <> RESpaces <> "&&" <> RESpaces <> reVar0 + , "(" <> RESpaces <> reVar0 <> RESpaces <> ")" + -- == { 0.1.2 } -- silly haddock: ^>= { 0.1.2, 3.4.5 } , "==" <> RESpaces <> verSet @@ -514,3 +537,10 @@ majorUpperBound = alterVersion $ \numbers -> case numbers of [] -> [0,1] -- should not happen [m1] -> [m1,1] -- e.g. version '1' (m1:m2:_) -> [m1,m2+1] + +-- | @since 2.2 +wildcardUpperBound :: Version -> Version +wildcardUpperBound = alterVersion $ + \lowerBound -> case unsnoc lowerBound of + Nothing -> [] + Just (xs, x) -> xs ++ [x + 1] diff --git a/Cabal/Distribution/Version.hs b/Cabal/Distribution/Version.hs index 06571b7fd0a349d6509f36ea890064900189969b..f2827590435e2a1d37bba2acaa32dabf55e92249 100644 --- a/Cabal/Distribution/Version.hs +++ b/Cabal/Distribution/Version.hs @@ -97,23 +97,6 @@ import Distribution.Types.VersionInterval -- Utilities on VersionRange requiring VersionInterval ------------------------------------------------------------------------------- --- | Does this 'VersionRange' place any restriction on the 'Version' or is it --- in fact equivalent to 'AnyVersion'. --- --- Note this is a semantic check, not simply a syntactic check. So for example --- the following is @True@ (for all @v@). --- --- > isAnyVersion (EarlierVersion v `UnionVersionRanges` orLaterVersion v) --- -isAnyVersion :: VersionRange -> Bool -isAnyVersion vr = case asVersionIntervals vr of - [(LowerBound v InclusiveBound, NoUpperBound)] | isVersion0 v -> True - _ -> False - where - isVersion0 :: Version -> Bool - isVersion0 = (== mkVersion [0]) - - -- | This is the converse of 'isAnyVersion'. It check if the version range is -- empty, if there is no possible version that satisfies the version range. -- diff --git a/Cabal/tests/ParserTests/regressions/Octree-0.5.expr b/Cabal/tests/ParserTests/regressions/Octree-0.5.expr index b3e2215c3d5e80cae14782c9cb42bc35557631b5..d8b7ed586443ecf127c0e390b5a0629230ab0fcc 100644 --- a/Cabal/tests/ParserTests/regressions/Octree-0.5.expr +++ b/Cabal/tests/ParserTests/regressions/Octree-0.5.expr @@ -202,7 +202,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "markdown-unlit"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite {testBuildInfo = BuildInfo @@ -276,7 +276,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "markdown-unlit"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/Octree-0.5.format b/Cabal/tests/ParserTests/regressions/Octree-0.5.format index db863ed59a966c1350986467c191cc2a2abc39a5..432c3bba9a468d07955238b94b98994b12d0fe8c 100644 --- a/Cabal/tests/ParserTests/regressions/Octree-0.5.format +++ b/Cabal/tests/ParserTests/regressions/Octree-0.5.format @@ -48,4 +48,4 @@ test-suite readme base >=4.0 && <4.7, AC-Vector >=2.3.0, QuickCheck >=2.4.0, - markdown-unlit -any + markdown-unlit diff --git a/Cabal/tests/ParserTests/regressions/common-conditional.expr b/Cabal/tests/ParserTests/regressions/common-conditional.expr index f6e194e31f4544c501a07e8e4144e3fe9daf309c..5dd69758109f154bae42e296ff26d41bd012a127 100644 --- a/Cabal/tests/ParserTests/regressions/common-conditional.expr +++ b/Cabal/tests/ParserTests/regressions/common-conditional.expr @@ -15,7 +15,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -72,7 +73,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -92,7 +94,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -158,7 +161,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -169,7 +173,7 @@ GenericPackageDescription signatures = []}}}], condTreeConstraints = [Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf"`], @@ -217,7 +221,8 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -305,7 +310,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite @@ -361,7 +367,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -377,7 +384,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite @@ -433,7 +441,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -453,7 +462,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite @@ -518,7 +528,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -529,7 +540,7 @@ GenericPackageDescription testName = `UnqualComponentName ""`}}}], condTreeConstraints = [Dependency `PackageName "HUnit"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite {testBuildInfo = BuildInfo @@ -579,7 +590,8 @@ GenericPackageDescription [] [], targetBuildDepends = [Dependency `PackageName "HUnit"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/common-conditional.format b/Cabal/tests/ParserTests/regressions/common-conditional.format index 5a9cdd13b6a889ab60864ea35205cfad36bfd1a1..b0f6551448fa744e68d42d7b832a6107578adc5a 100644 --- a/Cabal/tests/ParserTests/regressions/common-conditional.format +++ b/Cabal/tests/ParserTests/regressions/common-conditional.format @@ -14,20 +14,20 @@ flag foo library exposed-modules: ElseIf default-language: Haskell2010 - build-depends: ghc-prim -any + build-depends: ghc-prim if flag(foo) build-depends: base >=4.10 && <4.11, - containers -any + containers if os(windows) - build-depends: Win32 -any + build-depends: Win32 test-suite tests type: exitcode-stdio-1.0 main-is: Tests.hs - build-depends: HUnit -any + build-depends: HUnit if os(windows) buildable: False @@ -35,10 +35,10 @@ test-suite tests if flag(foo) build-depends: base >=4.10 && <4.11, - containers -any + containers if os(windows) - build-depends: Win32 -any + build-depends: Win32 if os(windows) - build-depends: Win32 -any + build-depends: Win32 diff --git a/Cabal/tests/ParserTests/regressions/common.expr b/Cabal/tests/ParserTests/regressions/common.expr index a22e1698c3da0e6f88bb7b66106ff30ee1b4a866..87cc61f39418bc38dd5801ff683abada11bce6af 100644 --- a/Cabal/tests/ParserTests/regressions/common.expr +++ b/Cabal/tests/ParserTests/regressions/common.expr @@ -7,7 +7,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf"`], @@ -55,7 +55,8 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -71,7 +72,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "HUnit"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite {testBuildInfo = BuildInfo @@ -121,7 +122,8 @@ GenericPackageDescription [] [], targetBuildDepends = [Dependency `PackageName "HUnit"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/common.format b/Cabal/tests/ParserTests/regressions/common.format index 22ce6dad4328c705f4611930a270f4d352a2de19..7fb317a16a56275eba47efbeafceff02e0e231fe 100644 --- a/Cabal/tests/ParserTests/regressions/common.format +++ b/Cabal/tests/ParserTests/regressions/common.format @@ -16,9 +16,9 @@ source-repository head library exposed-modules: ElseIf default-language: Haskell2010 - build-depends: ghc-prim -any + build-depends: ghc-prim test-suite tests type: exitcode-stdio-1.0 main-is: Tests.hs - build-depends: HUnit -any + build-depends: HUnit diff --git a/Cabal/tests/ParserTests/regressions/common2.expr b/Cabal/tests/ParserTests/regressions/common2.expr index c5603607e61b3d4d8db8c623c16446079b8d81ee..3f1dc4830e9fc6814eae9955b419681a7290ee95 100644 --- a/Cabal/tests/ParserTests/regressions/common2.expr +++ b/Cabal/tests/ParserTests/regressions/common2.expr @@ -11,7 +11,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -68,7 +69,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -85,11 +87,11 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf"`], @@ -146,12 +148,14 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -170,7 +174,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -227,7 +232,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -245,11 +251,11 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf2"`], @@ -309,12 +315,14 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -334,7 +342,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite @@ -390,7 +399,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -406,7 +416,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite @@ -462,7 +473,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -543,11 +555,11 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "HUnit"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite {testBuildInfo = BuildInfo @@ -606,12 +618,14 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "HUnit"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/common2.format b/Cabal/tests/ParserTests/regressions/common2.format index ba1434c24b776936e98367355130be3600c61c0f..3385e4f9a97dd7c0220e68c85a83e78336576080 100644 --- a/Cabal/tests/ParserTests/regressions/common2.format +++ b/Cabal/tests/ParserTests/regressions/common2.format @@ -13,36 +13,36 @@ library default-language: Haskell2010 build-depends: base >=4.10 && <4.11, - containers -any, - ghc-prim -any + containers, + ghc-prim if os(windows) - build-depends: Win32 -any + build-depends: Win32 library internal exposed-modules: ElseIf2 default-language: Haskell2010 build-depends: base >=4.10 && <4.11, - containers -any, - ghc-prim -any + containers, + ghc-prim if os(windows) - build-depends: Win32 -any + build-depends: Win32 test-suite tests type: exitcode-stdio-1.0 main-is: Tests.hs build-depends: base >=4.10 && <4.11, - containers -any, - HUnit -any + containers, + HUnit if os(windows) - build-depends: Win32 -any + build-depends: Win32 if os(windows) - build-depends: Win32 -any + build-depends: Win32 if os(windows) buildable: False diff --git a/Cabal/tests/ParserTests/regressions/common3.expr b/Cabal/tests/ParserTests/regressions/common3.expr index 1f0c2c3cfb172389a2b26edadface681bdddbd19..b5c677c1f416748dc0efbddddee9148f3515be77 100644 --- a/Cabal/tests/ParserTests/regressions/common3.expr +++ b/Cabal/tests/ParserTests/regressions/common3.expr @@ -7,7 +7,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf"`], @@ -55,7 +55,8 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -77,11 +78,11 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "HUnit"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite {testBuildInfo = BuildInfo @@ -140,12 +141,14 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "HUnit"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/common3.format b/Cabal/tests/ParserTests/regressions/common3.format index 4e367155e1dd07124f492b6389bdfc71912c9ce4..1911d0c64950b8cc77ae19428afe6558c3537a68 100644 --- a/Cabal/tests/ParserTests/regressions/common3.format +++ b/Cabal/tests/ParserTests/regressions/common3.format @@ -14,12 +14,12 @@ source-repository head library exposed-modules: ElseIf default-language: Haskell2010 - build-depends: ghc-prim -any + build-depends: ghc-prim test-suite tests type: exitcode-stdio-1.0 main-is: Tests.hs build-depends: base >=4.10 && <4.11, - containers -any, - HUnit -any + containers, + HUnit diff --git a/Cabal/tests/ParserTests/regressions/elif.expr b/Cabal/tests/ParserTests/regressions/elif.expr index 7f086f4f5527ef4b3fe218692f55ab1a68344d54..b35f55be5d0096f9c8fa0a1c4ac1634b0fb4f148 100644 --- a/Cabal/tests/ParserTests/regressions/elif.expr +++ b/Cabal/tests/ParserTests/regressions/elif.expr @@ -11,7 +11,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -68,7 +69,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/elif.format b/Cabal/tests/ParserTests/regressions/elif.format index e6cba2b39016ffec903b575b4b0b1a900bac6dc1..949d4432c1fd29941cc7dae8c7f6fcca0c3c3254 100644 --- a/Cabal/tests/ParserTests/regressions/elif.format +++ b/Cabal/tests/ParserTests/regressions/elif.format @@ -15,4 +15,4 @@ library default-language: Haskell2010 if os(linux) - build-depends: unix -any + build-depends: unix diff --git a/Cabal/tests/ParserTests/regressions/elif2.expr b/Cabal/tests/ParserTests/regressions/elif2.expr index f8add3a36d05d854e15dfb48ed1dab724573ba38..9c6fa9eca37fc0cd3c79615a4eddab43d286d82f 100644 --- a/Cabal/tests/ParserTests/regressions/elif2.expr +++ b/Cabal/tests/ParserTests/regressions/elif2.expr @@ -77,7 +77,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -134,7 +135,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "Win32"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -207,7 +209,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -264,7 +267,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/elif2.format b/Cabal/tests/ParserTests/regressions/elif2.format index b888676e14b004641169860ae2e6a31d3f25f5a0..616e45fbafa41cd9898579fc2897bd848faaaaaa 100644 --- a/Cabal/tests/ParserTests/regressions/elif2.format +++ b/Cabal/tests/ParserTests/regressions/elif2.format @@ -13,11 +13,11 @@ library default-language: Haskell2010 if os(linux) - build-depends: unix -any + build-depends: unix else if os(windows) - build-depends: Win32 -any + build-depends: Win32 else buildable: False diff --git a/Cabal/tests/ParserTests/regressions/encoding-0.8.expr b/Cabal/tests/ParserTests/regressions/encoding-0.8.expr index 8f6bcbcb51f9ec1b0f5906f744c285bb1367831f..99ee879da09b76eab6490122b313370af38f8f16 100644 --- a/Cabal/tests/ParserTests/regressions/encoding-0.8.expr +++ b/Cabal/tests/ParserTests/regressions/encoding-0.8.expr @@ -114,7 +114,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "ghc-prim"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])]}, sourceRepos = [], specVersion = CabalSpecV1_12, diff --git a/Cabal/tests/ParserTests/regressions/encoding-0.8.format b/Cabal/tests/ParserTests/regressions/encoding-0.8.format index d317e07bab8e08ea97219dbdeafdc1bc2d169048..161440209223732362fde6f947649a7974a401ca 100644 --- a/Cabal/tests/ParserTests/regressions/encoding-0.8.format +++ b/Cabal/tests/ParserTests/regressions/encoding-0.8.format @@ -11,7 +11,7 @@ extra-source-files: custom-setup setup-depends: base <5, - ghc-prim -any + ghc-prim library exposed-modules: Data.Encoding diff --git a/Cabal/tests/ParserTests/regressions/generics-sop.expr b/Cabal/tests/ParserTests/regressions/generics-sop.expr index 05cdf4c34feb6d1a3f09b71179b1b799a6f7221c..5b5f142fd01be37f049d1c79a626b8b87f3ae866 100644 --- a/Cabal/tests/ParserTests/regressions/generics-sop.expr +++ b/Cabal/tests/ParserTests/regressions/generics-sop.expr @@ -491,7 +491,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "doctest"` @@ -551,7 +551,8 @@ GenericPackageDescription [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -579,7 +580,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "generics-sop"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite {testBuildInfo = BuildInfo @@ -639,7 +640,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "generics-sop"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -704,11 +706,11 @@ GenericPackageDescription {defaultSetupDepends = False, setupDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "Cabal"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "cabal-doctest"` @@ -737,4 +739,8 @@ GenericPackageDescription _×_ GHC (ThisVersion `mkVersion [8,0,1]`), _×_ GHC (ThisVersion `mkVersion [8,0,2]`), _×_ GHC (ThisVersion `mkVersion [8,2,1]`), - _×_ GHC (WildcardVersion `mkVersion [8,3]`)]}} + _×_ + GHC + (IntersectVersionRanges + (OrLaterVersion `mkVersion [8,3]`) + (EarlierVersion `mkVersion [8,4]`))]}} diff --git a/Cabal/tests/ParserTests/regressions/generics-sop.format b/Cabal/tests/ParserTests/regressions/generics-sop.format index ceaa8ddee40fced1296c8299a9e69a53abeeb164..eaf3cf62dd6068f3f9d395add61984ae9c3bb9aa 100644 --- a/Cabal/tests/ParserTests/regressions/generics-sop.format +++ b/Cabal/tests/ParserTests/regressions/generics-sop.format @@ -9,7 +9,7 @@ author: tested-with: ghc ==7.8.4 ghc ==7.10.3 ghc ==8.0.1 ghc ==8.0.2 ghc ==8.2.1 - ghc ==8.3.* + ghc >=8.3 && <8.4 synopsis: Generic Programming using True Sums of Products description: @@ -51,8 +51,8 @@ source-repository head custom-setup setup-depends: - base -any, - Cabal -any, + base, + Cabal, cabal-doctest >=1.0.2 && <1.1 library @@ -114,7 +114,7 @@ test-suite doctests ghc-options: -Wall -threaded x-doctest-options: --preserve-it build-depends: - base -any, + base, doctest >=0.13 && <0.14 test-suite generics-sop-examples @@ -126,4 +126,4 @@ test-suite generics-sop-examples ghc-options: -Wall build-depends: base >=4.6 && <5, - generics-sop -any + generics-sop diff --git a/Cabal/tests/ParserTests/regressions/hidden-main-lib.expr b/Cabal/tests/ParserTests/regressions/hidden-main-lib.expr index 7aefae821683becb3eb3c1e1e53a4c78e952637c..e4ccd7652e2cd093ff45771aceee6250450980de 100644 --- a/Cabal/tests/ParserTests/regressions/hidden-main-lib.expr +++ b/Cabal/tests/ParserTests/regressions/hidden-main-lib.expr @@ -7,7 +7,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf"`], @@ -55,7 +55,8 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/hidden-main-lib.format b/Cabal/tests/ParserTests/regressions/hidden-main-lib.format index 62aeecaa190908c0808c5ae56e1711ac15be30cf..61c7fc4afca9c8a455f815f77825ae6e20e48c83 100644 --- a/Cabal/tests/ParserTests/regressions/hidden-main-lib.format +++ b/Cabal/tests/ParserTests/regressions/hidden-main-lib.format @@ -8,4 +8,4 @@ build-type: Simple library exposed-modules: ElseIf default-language: Haskell2010 - build-depends: base -any + build-depends: base diff --git a/Cabal/tests/ParserTests/regressions/issue-5846.expr b/Cabal/tests/ParserTests/regressions/issue-5846.expr index 1fa1522c0c9abc2f182321cc25f54e2af0f63584..363caa7c8958a47828445a887c43f14c12d2fd7d 100644 --- a/Cabal/tests/ParserTests/regressions/issue-5846.expr +++ b/Cabal/tests/ParserTests/regressions/issue-5846.expr @@ -7,13 +7,13 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "lib1"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LSubLibName `UnqualComponentName "a"`, LSubLibName `UnqualComponentName "b"`]), Dependency `PackageName "lib2"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LSubLibName `UnqualComponentName "c"`]), Dependency @@ -73,7 +73,8 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "lib1"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LSubLibName `UnqualComponentName "a"`, @@ -81,7 +82,8 @@ GenericPackageDescription `UnqualComponentName "b"`]), Dependency `PackageName "lib2"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LSubLibName `UnqualComponentName "c"`]), diff --git a/Cabal/tests/ParserTests/regressions/issue-5846.format b/Cabal/tests/ParserTests/regressions/issue-5846.format index 4efb60912924a8ea86c7f03ce608d4ff4d81b69a..f0e119da0c06fa47e95b7c97b7ad7dd4628ed500 100644 --- a/Cabal/tests/ParserTests/regressions/issue-5846.format +++ b/Cabal/tests/ParserTests/regressions/issue-5846.format @@ -9,7 +9,7 @@ version: 5846 library default-language: Haskell2010 build-depends: - lib1:{a, b} -any, - lib2:{c} -any, + lib1:{a, b}, + lib2:{c}, lib3:{d} >=1, lib4:{a, b} >=1 diff --git a/Cabal/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr b/Cabal/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr index 86306cd2509e057a7d97e5a79d38c9f3e6166671..9351d78c37ed4b0da28b8c2a01cf10e102bbe9e4 100644 --- a/Cabal/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr +++ b/Cabal/tests/ParserTests/regressions/issue-6083-pkg-pkg.expr @@ -7,11 +7,11 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "freetype"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "freetype"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [], @@ -59,12 +59,14 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "freetype"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "freetype"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/issue-6083-pkg-pkg.format b/Cabal/tests/ParserTests/regressions/issue-6083-pkg-pkg.format index 817f82a97a49e666a7407449538bd9070e34db42..7f8cf21586571f83bdffa26f66f1bc80a07225c6 100644 --- a/Cabal/tests/ParserTests/regressions/issue-6083-pkg-pkg.format +++ b/Cabal/tests/ParserTests/regressions/issue-6083-pkg-pkg.format @@ -6,5 +6,5 @@ version: 6083 library default-language: Haskell2010 build-depends: - freetype -any, - freetype -any + freetype, + freetype diff --git a/Cabal/tests/ParserTests/regressions/jaeger-flamegraph.expr b/Cabal/tests/ParserTests/regressions/jaeger-flamegraph.expr index 7765fe1cd264cfd69d3b8eb98f2dddc6a014ef99..58585c813a002adcdbc9c89d63d5f84ca6be2382 100644 --- a/Cabal/tests/ParserTests/regressions/jaeger-flamegraph.expr +++ b/Cabal/tests/ParserTests/regressions/jaeger-flamegraph.expr @@ -12,7 +12,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "jaeger-flamegraph"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "bytestring"` @@ -96,7 +96,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "jaeger-flamegraph"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -234,7 +235,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "jaeger-flamegraph"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "tasty"` @@ -309,7 +310,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "jaeger-flamegraph"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency diff --git a/Cabal/tests/ParserTests/regressions/jaeger-flamegraph.format b/Cabal/tests/ParserTests/regressions/jaeger-flamegraph.format index 3f8df9b0e13b1f8d87ea0e94ce9bc969eb6786c3..21f0adf1b543ed8a7d5aea168bd334e03c56f8e2 100644 --- a/Cabal/tests/ParserTests/regressions/jaeger-flamegraph.format +++ b/Cabal/tests/ParserTests/regressions/jaeger-flamegraph.format @@ -46,7 +46,7 @@ executable jaeger-flamegraph ghc-options: -Wall -Werror=missing-home-modules -threaded build-depends: base ^>=4.11.1.0 || ^>=4.12.0.0, - jaeger-flamegraph -any, + jaeger-flamegraph, bytestring ^>=0.10.8.2, containers ^>=0.6.0.1, extra ^>=1.6.13, @@ -64,7 +64,7 @@ test-suite tests ghc-options: -Wall -Werror=missing-home-modules -threaded build-depends: base ^>=4.11.1.0 || ^>=4.12.0.0, - jaeger-flamegraph -any, + jaeger-flamegraph, tasty ^>=1.1.0.4, tasty-hspec ^>=1.1.5, tasty-quickcheck ^>=0.10 diff --git a/Cabal/tests/ParserTests/regressions/leading-comma-2.expr b/Cabal/tests/ParserTests/regressions/leading-comma-2.expr index 179651d9db3843e061d9bb087107f8c389ce1ee7..10604d0e994495a68ddbc837027869f5de82da1b 100644 --- a/Cabal/tests/ParserTests/regressions/leading-comma-2.expr +++ b/Cabal/tests/ParserTests/regressions/leading-comma-2.expr @@ -7,27 +7,27 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "deepseq"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "transformers"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "LeadingComma"`, @@ -82,32 +82,38 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "deepseq"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "transformers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/leading-comma-2.format b/Cabal/tests/ParserTests/regressions/leading-comma-2.format index e69731528c01e17db59e51f1355152302deb3dbf..91c2bcd15131ffe4bad5e32ae0151506bea26004 100644 --- a/Cabal/tests/ParserTests/regressions/leading-comma-2.format +++ b/Cabal/tests/ParserTests/regressions/leading-comma-2.format @@ -17,9 +17,9 @@ library default-language: Haskell2010 build-depends: - base -any, - containers -any, - deepseq -any, - transformers -any, - filepath -any, - directory -any + base, + containers, + deepseq, + transformers, + filepath, + directory diff --git a/Cabal/tests/ParserTests/regressions/leading-comma.expr b/Cabal/tests/ParserTests/regressions/leading-comma.expr index 79a8a5119f0784b325270321df52ccf136cb94e0..fc399b6648c62c4dc9f0480a47e2eecc703c9121 100644 --- a/Cabal/tests/ParserTests/regressions/leading-comma.expr +++ b/Cabal/tests/ParserTests/regressions/leading-comma.expr @@ -7,27 +7,27 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "deepseq"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "transformers"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "LeadingComma"`], @@ -75,32 +75,38 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "deepseq"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "transformers"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/leading-comma.format b/Cabal/tests/ParserTests/regressions/leading-comma.format index b842c0e7bd942412e98864391b4c56459e582eaa..8736cfd942b0dd0b967ec62176ea86911896c70b 100644 --- a/Cabal/tests/ParserTests/regressions/leading-comma.format +++ b/Cabal/tests/ParserTests/regressions/leading-comma.format @@ -8,9 +8,9 @@ library exposed-modules: LeadingComma default-language: Haskell2010 build-depends: - base -any, - containers -any, - deepseq -any, - transformers -any, - filepath -any, - directory -any + base, + containers, + deepseq, + transformers, + filepath, + directory diff --git a/Cabal/tests/ParserTests/regressions/libpq1.expr b/Cabal/tests/ParserTests/regressions/libpq1.expr index 75cb8d915dc51c2f53f120e758fa94f36c437e83..510555211fbb0ddfd9e67ef7212997402ad2ae04 100644 --- a/Cabal/tests/ParserTests/regressions/libpq1.expr +++ b/Cabal/tests/ParserTests/regressions/libpq1.expr @@ -467,7 +467,7 @@ GenericPackageDescription otherExtensions = [], otherLanguages = [], otherModules = [], - pkgconfigDepends = [`PkgconfigDependency (PkgconfigName "libpq") (PcIntersectVersionRanges (PcUnionVersionRanges (PcThisVersion (PkgconfigVersion "9")) (PcLaterVersion (PkgconfigVersion "9"))) (PcEarlierVersion (PkgconfigVersion "10")))`], + pkgconfigDepends = [`PkgconfigDependency (PkgconfigName "libpq") (PcIntersectVersionRanges (PcOrLaterVersion (PkgconfigVersion "9")) (PcEarlierVersion (PkgconfigVersion "10")))`], profOptions = PerCompilerFlavor [] [], @@ -505,7 +505,7 @@ GenericPackageDescription autogenIncludes = [], autogenModules = [], buildToolDepends = [], - buildTools = [`LegacyExeDependency "hsc2hs" AnyVersion`], + buildTools = [`LegacyExeDependency "hsc2hs" (OrLaterVersion (mkVersion [0]))`], buildable = True, cSources = ["cbits/noticehandlers.c"], ccOptions = [], diff --git a/Cabal/tests/ParserTests/regressions/libpq1.format b/Cabal/tests/ParserTests/regressions/libpq1.format index c40e3ffd8dc53953c47942ecd77e2dbfc4851743..2326cd6740cb6686a7514451385b7390ab3ac94d 100644 --- a/Cabal/tests/ParserTests/regressions/libpq1.format +++ b/Cabal/tests/ParserTests/regressions/libpq1.format @@ -43,7 +43,7 @@ library Database.PostgreSQL.LibPQ Database.PostgreSQL.LibPQ.Internal - build-tools: hsc2hs -any + build-tools: hsc2hs >=0 c-sources: cbits/noticehandlers.c hs-source-dirs: src include-dirs: cbits @@ -59,7 +59,7 @@ library build-depends: Win32 >=2.2.0.2 && <2.7 if flag(use-pkg-config) - pkgconfig-depends: libpq (==9 || >9) && <10 + pkgconfig-depends: libpq >=9 && <10 else if os(windows) diff --git a/Cabal/tests/ParserTests/regressions/libpq2.expr b/Cabal/tests/ParserTests/regressions/libpq2.expr index 1e8e8f53a69b154a13999b5e8afcf9661185479b..d6f8ab4594fe15b61b2e55780b044b5165d24cc0 100644 --- a/Cabal/tests/ParserTests/regressions/libpq2.expr +++ b/Cabal/tests/ParserTests/regressions/libpq2.expr @@ -504,7 +504,7 @@ GenericPackageDescription asmSources = [], autogenIncludes = [], autogenModules = [], - buildToolDepends = [`ExeDependency (PackageName "hsc2hs") (UnqualComponentName "hsc2hs") AnyVersion`], + buildToolDepends = [`ExeDependency (PackageName "hsc2hs") (UnqualComponentName "hsc2hs") (OrLaterVersion (mkVersion [0]))`], buildTools = [], buildable = True, cSources = ["cbits/noticehandlers.c"], diff --git a/Cabal/tests/ParserTests/regressions/libpq2.format b/Cabal/tests/ParserTests/regressions/libpq2.format index 7a5b87e0ad7c4bc22a56092347cac0df4237ce02..596763d5ecd79ed0cb3f898ec900cbbf396cf1cf 100644 --- a/Cabal/tests/ParserTests/regressions/libpq2.format +++ b/Cabal/tests/ParserTests/regressions/libpq2.format @@ -43,7 +43,7 @@ library Database.PostgreSQL.LibPQ Database.PostgreSQL.LibPQ.Internal - build-tool-depends: hsc2hs:hsc2hs -any + build-tool-depends: hsc2hs:hsc2hs c-sources: cbits/noticehandlers.c hs-source-dirs: src include-dirs: cbits diff --git a/Cabal/tests/ParserTests/regressions/mixin-1.expr b/Cabal/tests/ParserTests/regressions/mixin-1.expr index 4f3c6bead04a32417db02648952563238f848907..c33b9ea200ba71403a32a845c828bbf6aeed9f2c 100644 --- a/Cabal/tests/ParserTests/regressions/mixin-1.expr +++ b/Cabal/tests/ParserTests/regressions/mixin-1.expr @@ -6,15 +6,15 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-string"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-bytestring"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Executable {buildInfo = BuildInfo @@ -62,17 +62,20 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-string"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-bytestring"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/mixin-1.format b/Cabal/tests/ParserTests/regressions/mixin-1.format index 5bf744429af830a2ad483d29997fae9925f9627e..129487155fae08a4b751a80e92005f93618d4ede 100644 --- a/Cabal/tests/ParserTests/regressions/mixin-1.format +++ b/Cabal/tests/ParserTests/regressions/mixin-1.format @@ -6,9 +6,9 @@ executable str-example main-is: Main.hs hs-source-dirs: str-example build-depends: - base -any, - str-string -any, - str-bytestring -any + base, + str-string, + str-bytestring mixins: str-string (Str as Str.String), diff --git a/Cabal/tests/ParserTests/regressions/mixin-2.expr b/Cabal/tests/ParserTests/regressions/mixin-2.expr index 8d95873cebe94c44dd3f8a0e5400bc1e8158cfe2..e1e57661dc145054e6c0e4601276f77351876bf8 100644 --- a/Cabal/tests/ParserTests/regressions/mixin-2.expr +++ b/Cabal/tests/ParserTests/regressions/mixin-2.expr @@ -6,15 +6,15 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-string"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-bytestring"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Executable {buildInfo = BuildInfo @@ -62,17 +62,20 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-string"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-bytestring"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/mixin-2.format b/Cabal/tests/ParserTests/regressions/mixin-2.format index 22517fa11fd377691dab3e4bec6b3ffbf8437903..9aeeec704ab1477dfb9a7d5cc2db228ff31a2d2c 100644 --- a/Cabal/tests/ParserTests/regressions/mixin-2.format +++ b/Cabal/tests/ParserTests/regressions/mixin-2.format @@ -6,9 +6,9 @@ executable str-example main-is: Main.hs hs-source-dirs: str-example build-depends: - base -any, - str-string -any, - str-bytestring -any + base, + str-string, + str-bytestring mixins: str-string (Str as Str.String), diff --git a/Cabal/tests/ParserTests/regressions/mixin-3.expr b/Cabal/tests/ParserTests/regressions/mixin-3.expr index 00b49008b08c1a0796a0e0ce0ef72eae6539746d..cefbf9d45e15c1b1b7adacb5cacd0fb0bf140706 100644 --- a/Cabal/tests/ParserTests/regressions/mixin-3.expr +++ b/Cabal/tests/ParserTests/regressions/mixin-3.expr @@ -6,15 +6,15 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-string"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-bytestring"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Executable {buildInfo = BuildInfo @@ -61,17 +61,20 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-string"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "str-bytestring"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/mixin-3.format b/Cabal/tests/ParserTests/regressions/mixin-3.format index 9b2968f436054ab29f9a344b044129b7a4c467e6..b40dbd964d5fe0293add90b5e7145898f726036b 100644 --- a/Cabal/tests/ParserTests/regressions/mixin-3.format +++ b/Cabal/tests/ParserTests/regressions/mixin-3.format @@ -6,8 +6,8 @@ executable str-example main-is: Main.hs hs-source-dirs: str-example build-depends: - base -any, - str-string -any, - str-bytestring -any + base, + str-string, + str-bytestring mixins: str hiding (Foo) diff --git a/Cabal/tests/ParserTests/regressions/multiple-libs-2.expr b/Cabal/tests/ParserTests/regressions/multiple-libs-2.expr index 02e6abbc131dddb13e75f34461ae742ef468435e..ff18de89d9a84c0884a857ad4c07f0fe56579122 100644 --- a/Cabal/tests/ParserTests/regressions/multiple-libs-2.expr +++ b/Cabal/tests/ParserTests/regressions/multiple-libs-2.expr @@ -7,7 +7,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf"`], @@ -55,7 +55,8 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -70,7 +71,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf2"`], @@ -121,7 +122,8 @@ GenericPackageDescription [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/multiple-libs-2.format b/Cabal/tests/ParserTests/regressions/multiple-libs-2.format index aba24b3c2a8417c1a767dea6ca469221ed958700..2cc3d5a6556c86889769e6bc4160b2b111eeabc8 100644 --- a/Cabal/tests/ParserTests/regressions/multiple-libs-2.format +++ b/Cabal/tests/ParserTests/regressions/multiple-libs-2.format @@ -8,9 +8,9 @@ build-type: Simple library exposed-modules: ElseIf default-language: Haskell2010 - build-depends: base -any + build-depends: base library public exposed-modules: ElseIf2 default-language: Haskell2010 - build-depends: base -any + build-depends: base diff --git a/Cabal/tests/ParserTests/regressions/noVersion.expr b/Cabal/tests/ParserTests/regressions/noVersion.expr index e13acdca503c66352378fc84170214e179e6e0f7..8f463889111b9affca58961f3fc1a270f4ffbcbd 100644 --- a/Cabal/tests/ParserTests/regressions/noVersion.expr +++ b/Cabal/tests/ParserTests/regressions/noVersion.expr @@ -7,9 +7,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "bad-package"` - (IntersectVersionRanges - (LaterVersion `mkVersion [1]`) - (EarlierVersion `mkVersion [1]`)) + (EarlierVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library {exposedModules = [`ModuleName "ElseIf"`], @@ -57,11 +55,8 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "bad-package"` - (IntersectVersionRanges - (LaterVersion - `mkVersion [1]`) - (EarlierVersion - `mkVersion [1]`)) + (EarlierVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/noVersion.format b/Cabal/tests/ParserTests/regressions/noVersion.format index 5847397dbefe096c71a12a0d8bacbba50d321f41..b688d5caddc7d2985d78b1d55aa3c0ea491d5cd4 100644 --- a/Cabal/tests/ParserTests/regressions/noVersion.format +++ b/Cabal/tests/ParserTests/regressions/noVersion.format @@ -7,4 +7,4 @@ build-type: Simple library exposed-modules: ElseIf default-language: Haskell2010 - build-depends: bad-package >1 && <1 + build-depends: bad-package <0 diff --git a/Cabal/tests/ParserTests/regressions/shake.expr b/Cabal/tests/ParserTests/regressions/shake.expr index 5fb1a3777ebef287a7599f829248e7bf9c70b3b4..859147f4ce2d9351e78627f1152b30a1b45910c0 100644 --- a/Cabal/tests/ParserTests/regressions/shake.expr +++ b/Cabal/tests/ParserTests/regressions/shake.expr @@ -207,7 +207,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "old-time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Executable @@ -263,7 +264,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "old-time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -334,7 +336,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Executable @@ -390,7 +393,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -399,11 +403,13 @@ GenericPackageDescription modulePath = ""}}}], condTreeConstraints = [Dependency `PackageName "base"` - (WildcardVersion `mkVersion [4]`) + (IntersectVersionRanges + (OrLaterVersion `mkVersion [4]`) + (EarlierVersion `mkVersion [5]`)) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "hashable"` @@ -411,11 +417,11 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "binary"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "process"` @@ -427,7 +433,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "bytestring"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "utf8-string"` @@ -435,19 +441,19 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "time"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "random"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-jquery"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-flot"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "transformers"` @@ -463,7 +469,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "primitive"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Executable {buildInfo = BuildInfo @@ -568,13 +574,17 @@ GenericPackageDescription staticOptions = PerCompilerFlavor [] [], targetBuildDepends = [Dependency `PackageName "base"` - (WildcardVersion - `mkVersion [4]`) + (IntersectVersionRanges + (OrLaterVersion + `mkVersion [4]`) + (EarlierVersion + `mkVersion [5]`)) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -585,12 +595,14 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "binary"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -607,7 +619,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "bytestring"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -618,22 +631,26 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "random"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-jquery"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-flot"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -656,7 +673,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "primitive"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -813,7 +831,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "old-time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -870,7 +889,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "old-time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -946,7 +966,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Library @@ -1003,7 +1024,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -1018,7 +1040,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "hashable"` @@ -1026,11 +1048,11 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "binary"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "process"` @@ -1042,7 +1064,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "bytestring"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "utf8-string"` @@ -1050,19 +1072,19 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "time"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "random"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-jquery"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-flot"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "transformers"` @@ -1176,7 +1198,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -1187,12 +1210,14 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "binary"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -1209,7 +1234,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "bytestring"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -1220,22 +1246,26 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "random"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-jquery"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-flot"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -1539,7 +1569,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "old-time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite @@ -1595,7 +1626,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "old-time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -1670,7 +1702,8 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite @@ -1726,7 +1759,8 @@ GenericPackageDescription [], targetBuildDepends = [Dependency `PackageName "unix"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, @@ -1737,11 +1771,13 @@ GenericPackageDescription testName = `UnqualComponentName ""`}}}], condTreeConstraints = [Dependency `PackageName "base"` - (WildcardVersion `mkVersion [4]`) + (IntersectVersionRanges + (OrLaterVersion `mkVersion [4]`) + (EarlierVersion `mkVersion [5]`)) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "hashable"` @@ -1749,11 +1785,11 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "binary"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "process"` @@ -1765,7 +1801,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "bytestring"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "utf8-string"` @@ -1773,19 +1809,19 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "time"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "random"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-jquery"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-flot"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "transformers"` @@ -1950,13 +1986,17 @@ GenericPackageDescription [] [], targetBuildDepends = [Dependency `PackageName "base"` - (WildcardVersion - `mkVersion [4]`) + (IntersectVersionRanges + (OrLaterVersion + `mkVersion [4]`) + (EarlierVersion + `mkVersion [5]`)) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -1967,12 +2007,14 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "binary"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -1989,7 +2031,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "bytestring"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -2000,22 +2043,26 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "time"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "random"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-jquery"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "js-flot"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency diff --git a/Cabal/tests/ParserTests/regressions/shake.format b/Cabal/tests/ParserTests/regressions/shake.format index fab4abcc5b28bd995ca670fa64463aa52e753b13..e52a8f3a4537abc0bf39a96c4fccc82fb6558406 100644 --- a/Cabal/tests/ParserTests/regressions/shake.format +++ b/Cabal/tests/ParserTests/regressions/shake.format @@ -143,18 +143,18 @@ library default-language: Haskell2010 build-depends: base >=4.5, - directory -any, + directory, hashable >=1.1.2.3, - binary -any, - filepath -any, + binary, + filepath, process >=1.1, unordered-containers >=0.2.1, - bytestring -any, + bytestring, utf8-string >=0.3, - time -any, - random -any, - js-jquery -any, - js-flot -any, + time, + random, + js-jquery, + js-flot, transformers >=0.2, extra >=1.4.8, deepseq >=1.1 @@ -163,14 +163,14 @@ library cpp-options: -DPORTABLE if impl(ghc <7.6) - build-depends: old-time -any + build-depends: old-time else if !os(windows) build-depends: unix >=2.5.1 if !os(windows) - build-depends: unix -any + build-depends: unix executable shake main-is: Run.hs @@ -235,23 +235,23 @@ executable shake default-language: Haskell2010 ghc-options: -main-is Run.main -rtsopts build-depends: - base ==4.*, - directory -any, + base >=4 && <5, + directory, hashable >=1.1.2.3, - binary -any, - filepath -any, + binary, + filepath, process >=1.1, unordered-containers >=0.2.1, - bytestring -any, + bytestring, utf8-string >=0.3, - time -any, - random -any, - js-jquery -any, - js-flot -any, + time, + random, + js-jquery, + js-flot, transformers >=0.2, extra >=1.4.8, deepseq >=1.1, - primitive -any + primitive if impl(ghc >=7.8) ghc-options: -threaded "-with-rtsopts=-I0 -qg -qb" @@ -260,14 +260,14 @@ executable shake cpp-options: -DPORTABLE if impl(ghc <7.6) - build-depends: old-time -any + build-depends: old-time else if !os(windows) build-depends: unix >=2.5.1 if !os(windows) - build-depends: unix -any + build-depends: unix test-suite shake-test type: exitcode-stdio-1.0 @@ -374,19 +374,19 @@ test-suite shake-test default-language: Haskell2010 ghc-options: -main-is Test.main -rtsopts build-depends: - base ==4.*, - directory -any, + base >=4 && <5, + directory, hashable >=1.1.2.3, - binary -any, - filepath -any, + binary, + filepath, process >=1.1, unordered-containers >=0.2.1, - bytestring -any, + bytestring, utf8-string >=0.3, - time -any, - random -any, - js-jquery -any, - js-flot -any, + time, + random, + js-jquery, + js-flot, transformers >=0.2, deepseq >=1.1, extra >=1.4.8, @@ -402,11 +402,11 @@ test-suite shake-test cpp-options: -DPORTABLE if impl(ghc <7.6) - build-depends: old-time -any + build-depends: old-time else if !os(windows) build-depends: unix >=2.5.1 if !os(windows) - build-depends: unix -any + build-depends: unix diff --git a/Cabal/tests/ParserTests/regressions/th-lift-instances.expr b/Cabal/tests/ParserTests/regressions/th-lift-instances.expr index be1369dc89abcc203672847629dcb5a8a2d7e496..370d3b2da9faddfd73341d90614f837f58367a11 100644 --- a/Cabal/tests/ParserTests/regressions/th-lift-instances.expr +++ b/Cabal/tests/ParserTests/regressions/th-lift-instances.expr @@ -17,7 +17,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "th-lift"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "containers"` @@ -106,7 +106,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "th-lift"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -158,7 +159,7 @@ GenericPackageDescription {condTreeComponents = [], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "template-haskell"` @@ -190,7 +191,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "th-lift-instances"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "QuickCheck"` @@ -247,7 +248,8 @@ GenericPackageDescription [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -294,7 +296,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "th-lift-instances"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -379,7 +382,7 @@ GenericPackageDescription testName = `UnqualComponentName ""`}}}], condTreeConstraints = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency `PackageName "directory"` @@ -391,7 +394,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = TestSuite {testBuildInfo = BuildInfo @@ -443,7 +446,8 @@ GenericPackageDescription [] [], targetBuildDepends = [Dependency `PackageName "base"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName]), Dependency @@ -460,7 +464,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "filepath"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/th-lift-instances.format b/Cabal/tests/ParserTests/regressions/th-lift-instances.format index 7d9ab8be087379070dda5454864a85440a78d925..df2f77dd729af16ba2cbb44e73a143514d220981 100644 --- a/Cabal/tests/ParserTests/regressions/th-lift-instances.format +++ b/Cabal/tests/ParserTests/regressions/th-lift-instances.format @@ -38,7 +38,7 @@ library build-depends: base >=4.4 && <5, template-haskell <2.10, - th-lift -any, + th-lift, containers >=0.4 && <0.6, vector >=0.9 && <0.11, text >=0.11 && <1.3, @@ -52,13 +52,13 @@ test-suite tests default-language: Haskell2010 other-extensions: TemplateHaskell build-depends: - base -any, + base, template-haskell <2.10, containers >=0.4 && <0.6, vector >=0.9 && <0.11, text >=0.11 && <1.2, bytestring >=0.9 && <0.11, - th-lift-instances -any, + th-lift-instances, QuickCheck >=2.6 && <2.8 test-suite doctests @@ -68,10 +68,10 @@ test-suite doctests default-language: Haskell2010 ghc-options: -Wall -threaded build-depends: - base -any, + base, directory >=1.0, doctest >=0.9.1, - filepath -any + filepath if impl(ghc <7.6.1) ghc-options: -Werror diff --git a/Cabal/tests/ParserTests/regressions/wl-pprint-indef.expr b/Cabal/tests/ParserTests/regressions/wl-pprint-indef.expr index 7aebf758d441332743a74d4d456a67bbc4d1bc6f..226d74cdd76ca0e8cb4c3be05998ede75af529f7 100644 --- a/Cabal/tests/ParserTests/regressions/wl-pprint-indef.expr +++ b/Cabal/tests/ParserTests/regressions/wl-pprint-indef.expr @@ -14,7 +14,7 @@ GenericPackageDescription (Set.fromList [LMainLibName]), Dependency `PackageName "wl-pprint-indef"` - AnyVersion + (OrLaterVersion `mkVersion [0]`) (Set.fromList [LMainLibName])], condTreeData = Executable {buildInfo = BuildInfo @@ -73,7 +73,8 @@ GenericPackageDescription [LMainLibName]), Dependency `PackageName "wl-pprint-indef"` - AnyVersion + (OrLaterVersion + `mkVersion [0]`) (Set.fromList [LMainLibName])], virtualModules = []}, diff --git a/Cabal/tests/ParserTests/regressions/wl-pprint-indef.format b/Cabal/tests/ParserTests/regressions/wl-pprint-indef.format index c2bcddfcbcbfc6b240b694b04908d7e70ba89504..1a16e964b06412450ca09c68a88b4da1b43dea2b 100644 --- a/Cabal/tests/ParserTests/regressions/wl-pprint-indef.format +++ b/Cabal/tests/ParserTests/regressions/wl-pprint-indef.format @@ -34,4 +34,4 @@ executable wl-pprint-string-example build-depends: base <5, str-string >=0.1.0.0, - wl-pprint-indef -any + wl-pprint-indef diff --git a/Cabal/tests/UnitTests/Distribution/Utils/Structured.hs b/Cabal/tests/UnitTests/Distribution/Utils/Structured.hs index 2d79813b156567661472f86c60c62c7ff9ad8c3c..f6310c307fab30a5252597e93fe8d6dfbbdd5d12 100644 --- a/Cabal/tests/UnitTests/Distribution/Utils/Structured.hs +++ b/Cabal/tests/UnitTests/Distribution/Utils/Structured.hs @@ -19,10 +19,10 @@ import UnitTests.Orphans () tests :: TestTree tests = testGroup "Distribution.Utils.Structured" -- This test also verifies that structureHash doesn't loop. - [ testCase "VersionRange" $ structureHash (Proxy :: Proxy VersionRange) @?= Fingerprint 0x6a33c568c9307696 0xe383268b2389a958 + [ testCase "VersionRange" $ structureHash (Proxy :: Proxy VersionRange) @?= Fingerprint 0x39396fc4f2d751aa 0xa1f94e6d843f03bd , testCase "SPDX.License" $ structureHash (Proxy :: Proxy License) @?= Fingerprint 0xd3d4a09f517f9f75 0xbc3d16370d5a853a -- The difference is in encoding of newtypes #if MIN_VERSION_base(4,7,0) - , testCase "LocalBuildInfo" $ structureHash (Proxy :: Proxy LocalBuildInfo) @?= Fingerprint 0x27de6f0a3d133e71 0x81c8d35b9e4b8bf0 + , testCase "LocalBuildInfo" $ structureHash (Proxy :: Proxy LocalBuildInfo) @?= Fingerprint 0x779513b2e8a07958 0xd344652f7031f88f #endif ] diff --git a/Cabal/tests/UnitTests/Distribution/Version.hs b/Cabal/tests/UnitTests/Distribution/Version.hs index 58b3d3edfe3ef4740c119921aad6e29d88a44722..02a5cc51d3e21035ac8920b74bd8374b5d62abf5 100644 --- a/Cabal/tests/UnitTests/Distribution/Version.hs +++ b/Cabal/tests/UnitTests/Distribution/Version.hs @@ -255,10 +255,11 @@ prop_invertVersionRange vr v' = withinRange v' (invertVersionRange vr) == not (withinRange v' vr) -prop_withinVersion :: Version -> Version -> Bool +prop_withinVersion :: Version -> Version -> Property prop_withinVersion v v' = - withinRange v' (withinVersion v) - == (v' >= v && v' < upper v) + withinRange v' (withinVersion v) + === + (v' >= v && v' < upper v) where upper = alterVersion $ \numbers -> case unsnoc numbers of Nothing -> [] @@ -272,8 +273,6 @@ prop_foldVersionRange range = unionVersionRanges intersectVersionRanges range where - expandVR (WildcardVersion v) = - intersectVersionRanges (expandVR (orLaterVersion v)) (earlierVersion (wildcardUpperBound v)) expandVR (MajorBoundVersion v) = intersectVersionRanges (expandVR (orLaterVersion v)) (earlierVersion (majorUpperBound v)) expandVR (OrEarlierVersion v) = @@ -643,13 +642,11 @@ displayRaw = -- precedence: -- All the same as the usual pretty printer, except for the parens - alg AnyVersionF = Disp.text "-any" alg (ThisVersionF v) = Disp.text "==" <<>> pretty v alg (LaterVersionF v) = Disp.char '>' <<>> pretty v alg (EarlierVersionF v) = Disp.char '<' <<>> pretty v alg (OrLaterVersionF v) = Disp.text ">=" <<>> pretty v alg (OrEarlierVersionF v) = Disp.text "<=" <<>> pretty v - alg (WildcardVersionF v) = Disp.text "==" <<>> dispWild v alg (MajorBoundVersionF v) = Disp.text "^>=" <<>> pretty v alg (UnionVersionRangesF r1 r2) = r1 <+> Disp.text "||" <+> r2 alg (IntersectVersionRangesF r1 r2) = r1 <+> Disp.text "&&" <+> r2 diff --git a/cabal-testsuite/PackageTests/Backpack/Includes2/cabal-internal.out b/cabal-testsuite/PackageTests/Backpack/Includes2/cabal-internal.out index 64df9b091449ff7e35bd74ff43a0b985e9244417..1f7c41475bc0d4ea35ed991ab859c8116a33b662 100644 --- a/cabal-testsuite/PackageTests/Backpack/Includes2/cabal-internal.out +++ b/cabal-testsuite/PackageTests/Backpack/Includes2/cabal-internal.out @@ -34,11 +34,11 @@ Building library 'mylib' instantiated with Database = Includes2-0.1.0.0-inplace-postgresql:Database.PostgreSQL for Includes2-0.1.0.0.. Configuring library for Includes2-0.1.0.0.. -Warning: The package has an extraneous version range for a dependency on an internal library: Includes2 -any && ==0.1.0.0 && ==0.1.0.0 && ==0.1.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: Includes2 >=0 && ==0.1.0.0 && ==0.1.0.0 && ==0.1.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing library for Includes2-0.1.0.0.. Building library for Includes2-0.1.0.0.. Configuring executable 'exe' for Includes2-0.1.0.0.. -Warning: The package has an extraneous version range for a dependency on an internal library: Includes2 -any && ==0.1.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: Includes2 >=0 && ==0.1.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing executable 'exe' for Includes2-0.1.0.0.. Building executable 'exe' for Includes2-0.1.0.0.. # Includes2 exe diff --git a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary1/cabal.out b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary1/cabal.out index ba8ddb98c9583f8cbd870e00ac93880329e406d1..1aa2d34312e4e4c404e6618d4913e3d27138ab6f 100644 --- a/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary1/cabal.out +++ b/cabal-testsuite/PackageTests/BuildDeps/InternalLibrary1/cabal.out @@ -8,6 +8,6 @@ Configuring library for InternalLibrary1-0.1.. Preprocessing library for InternalLibrary1-0.1.. Building library for InternalLibrary1-0.1.. Configuring executable 'lemon' for InternalLibrary1-0.1.. -Warning: The package has an extraneous version range for a dependency on an internal library: InternalLibrary1 -any && ==0.1. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: InternalLibrary1 >=0 && ==0.1. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing executable 'lemon' for InternalLibrary1-0.1.. Building executable 'lemon' for InternalLibrary1-0.1.. diff --git a/cabal-testsuite/PackageTests/BuildTools/Internal/cabal.out b/cabal-testsuite/PackageTests/BuildTools/Internal/cabal.out index d3c6bbd5ec06c6b91e81f9f00b5db52cc49e2a7d..29655811a97752a8b96053d47da61462194f2f39 100644 --- a/cabal-testsuite/PackageTests/BuildTools/Internal/cabal.out +++ b/cabal-testsuite/PackageTests/BuildTools/Internal/cabal.out @@ -12,6 +12,6 @@ Configuring library for foo-0.1.0.0.. Preprocessing library for foo-0.1.0.0.. Building library for foo-0.1.0.0.. Configuring executable 'hello-world' for foo-0.1.0.0.. -Warning: The package has an extraneous version range for a dependency on an internal library: foo -any && ==0.1.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: foo >=0 && ==0.1.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing executable 'hello-world' for foo-0.1.0.0.. Building executable 'hello-world' for foo-0.1.0.0.. diff --git a/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out b/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out index b84252dcd0080a411bb37e42179a4a12a2cb3bfa..bb0cc0d4bbc5069170d7f236321e0056442c1a78 100644 --- a/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out +++ b/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out @@ -10,4 +10,4 @@ Registering library 'sublib' for Lib-0.1.0.0.. # Setup configure Configuring executable 'exe' for Lib-0.1.0.0.. setup: Encountered missing or private dependencies: - sublib -any + sublib diff --git a/cabal-testsuite/PackageTests/Regression/T5309/cabal.out b/cabal-testsuite/PackageTests/Regression/T5309/cabal.out index e73dc9b85aa9985a3f5406aea209a0e0cbef305a..c1ce1436805ca34502d43b1cfe10083dd82d416e 100644 --- a/cabal-testsuite/PackageTests/Regression/T5309/cabal.out +++ b/cabal-testsuite/PackageTests/Regression/T5309/cabal.out @@ -12,7 +12,7 @@ Configuring executable 'exe-no-lib' for T5309-1.0.0.0.. Preprocessing executable 'exe-no-lib' for T5309-1.0.0.0.. Building executable 'exe-no-lib' for T5309-1.0.0.0.. Configuring executable 'exe-with-lib' for T5309-1.0.0.0.. -Warning: The package has an extraneous version range for a dependency on an internal library: T5309 -any && ==1.0.0.0, T5309 -any && ==1.0.0.0, T5309 -any && ==1.0.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: T5309 >=0 && ==1.0.0.0, T5309 >=0 && ==1.0.0.0, T5309 >=0 && ==1.0.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing executable 'exe-with-lib' for T5309-1.0.0.0.. Building executable 'exe-with-lib' for T5309-1.0.0.0.. # cabal v2-test @@ -29,7 +29,7 @@ Test suite test-no-lib: PASS Test suite logged to: <ROOT>/cabal.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/T5309-1.0.0.0/t/test-no-lib/test/T5309-1.0.0.0-test-no-lib.log 1 of 1 test suites (1 of 1 test cases) passed. Configuring test suite 'test-with-lib' for T5309-1.0.0.0.. -Warning: The package has an extraneous version range for a dependency on an internal library: T5309 -any && ==1.0.0.0, T5309 -any && ==1.0.0.0, T5309 -any && ==1.0.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: T5309 >=0 && ==1.0.0.0, T5309 >=0 && ==1.0.0.0, T5309 >=0 && ==1.0.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing test suite 'test-with-lib' for T5309-1.0.0.0.. Building test suite 'test-with-lib' for T5309-1.0.0.0.. Running 1 test suites... @@ -49,7 +49,7 @@ Running 1 benchmarks... Benchmark bench-no-lib: RUNNING... Benchmark bench-no-lib: FINISH Configuring benchmark 'bench-with-lib' for T5309-1.0.0.0.. -Warning: The package has an extraneous version range for a dependency on an internal library: T5309 -any && ==1.0.0.0, T5309 -any && ==1.0.0.0, T5309 -any && ==1.0.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: T5309 >=0 && ==1.0.0.0, T5309 >=0 && ==1.0.0.0, T5309 >=0 && ==1.0.0.0. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing benchmark 'bench-with-lib' for T5309-1.0.0.0.. Building benchmark 'bench-with-lib' for T5309-1.0.0.0.. Running 1 benchmarks... diff --git a/cabal-testsuite/PackageTests/Regression/T5677/cabal.out b/cabal-testsuite/PackageTests/Regression/T5677/cabal.out index c349e08bb9f07024f44c0e8d36a82496f85f2e96..aec1f55ca456024698e5eb0802d40e27f8b9a932 100644 --- a/cabal-testsuite/PackageTests/Regression/T5677/cabal.out +++ b/cabal-testsuite/PackageTests/Regression/T5677/cabal.out @@ -24,6 +24,6 @@ Preprocessing library for prog-0.. Building library instantiated with Sig = impl-0-inplace:Sig for prog-0.. Configuring executable 'prog' for prog-0.. -Warning: The package has an extraneous version range for a dependency on an internal library: prog -any && ==0. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: prog >=0 && ==0. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing executable 'prog' for prog-0.. Building executable 'prog' for prog-0.. diff --git a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/cabal.out b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/cabal.out index 7bff7ab154d9418b5c638b4e57d960b3fc0cdb54..083b069f225f1d341628f9f797252f599d8634e1 100644 --- a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/cabal.out +++ b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/cabal.out @@ -9,7 +9,7 @@ Configuring library for my-0.1.. Preprocessing library for my-0.1.. Building library for my-0.1.. Configuring test suite 'test-Short' for my-0.1.. -Warning: The package has an extraneous version range for a dependency on an internal library: my -any && ==0.1, my -any && ==0.1. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: my >=0 && ==0.1, my >=0 && ==0.1. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing test suite 'test-Short' for my-0.1.. Building test suite 'test-Short' for my-0.1.. Running 1 test suites... @@ -18,7 +18,7 @@ Test suite test-Short: PASS Test suite logged to: <ROOT>/cabal.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/my-0.1/t/test-Short/test/my-0.1-test-Short.log 1 of 1 test suites (1 of 1 test cases) passed. Configuring test suite 'test-Foo' for my-0.1.. -Warning: The package has an extraneous version range for a dependency on an internal library: my -any && ==0.1, my -any && ==0.1. This version range includes the current package but isn't needed as the current package's library will always be used. +Warning: The package has an extraneous version range for a dependency on an internal library: my >=0 && ==0.1, my >=0 && ==0.1. This version range includes the current package but isn't needed as the current package's library will always be used. Preprocessing test suite 'test-Foo' for my-0.1.. Building test suite 'test-Foo' for my-0.1.. Running 1 test suites...