diff --git a/Cabal/Distribution/CabalSpecVersion.hs b/Cabal/Distribution/CabalSpecVersion.hs index ccb34b356750ba1f3bdbfb911bb402efdee5c9a2..f53d999ae66fd67b5805f04d957cde5fd08a478b 100644 --- a/Cabal/Distribution/CabalSpecVersion.hs +++ b/Cabal/Distribution/CabalSpecVersion.hs @@ -4,14 +4,22 @@ module Distribution.CabalSpecVersion where import Prelude () import Distribution.Compat.Prelude -import qualified Data.Set as Set -- | Different Cabal-the-spec versions. -- -- We branch based on this at least in the parser. -- data CabalSpecVersion - = CabalSpecOld + = CabalSpecV1_0 -- ^ this is older than 'CabalSpecV1_2' + | CabalSpecV1_2 -- ^ new syntax (sections) + | CabalSpecV1_4 + | CabalSpecV1_6 + | CabalSpecV1_8 + | CabalSpecV1_10 + | CabalSpecV1_12 + -- 1.16 -- 1.14: no changes + | CabalSpecV1_18 + | CabalSpecV1_20 | CabalSpecV1_22 | CabalSpecV1_24 | CabalSpecV2_0 @@ -20,69 +28,64 @@ data CabalSpecVersion | CabalSpecV3_0 deriving (Eq, Ord, Show, Read, Enum, Bounded, Typeable, Data, Generic) +-- | Show cabal spec version, but not the way in the .cabal files +-- +-- @since 3.0.0.0 +showCabalSpecVersion :: CabalSpecVersion -> String +showCabalSpecVersion CabalSpecV3_0 = "3.0" +showCabalSpecVersion CabalSpecV2_4 = "2.4" +showCabalSpecVersion CabalSpecV2_2 = "2.2" +showCabalSpecVersion CabalSpecV2_0 = "2.0" +showCabalSpecVersion CabalSpecV1_24 = "1.24" +showCabalSpecVersion CabalSpecV1_22 = "1.22" +showCabalSpecVersion CabalSpecV1_20 = "1.20" +showCabalSpecVersion CabalSpecV1_18 = "1.18" +showCabalSpecVersion CabalSpecV1_12 = "1.12" +showCabalSpecVersion CabalSpecV1_10 = "1.10" +showCabalSpecVersion CabalSpecV1_8 = "1.8" +showCabalSpecVersion CabalSpecV1_6 = "1.6" +showCabalSpecVersion CabalSpecV1_4 = "1.4" +showCabalSpecVersion CabalSpecV1_2 = "1.2" +showCabalSpecVersion CabalSpecV1_0 = "1.0" + cabalSpecLatest :: CabalSpecVersion cabalSpecLatest = CabalSpecV3_0 -cabalSpecFeatures :: CabalSpecVersion -> Set.Set CabalFeature -cabalSpecFeatures CabalSpecOld = Set.empty -cabalSpecFeatures CabalSpecV1_22 = Set.empty -cabalSpecFeatures CabalSpecV1_24 = Set.empty -cabalSpecFeatures CabalSpecV2_0 = Set.empty -cabalSpecFeatures CabalSpecV2_2 = Set.fromList - [ Elif - , CommonStanzas - ] -cabalSpecFeatures CabalSpecV2_4 = Set.fromList - [ Elif - , CommonStanzas - , Globstar - ] -cabalSpecFeatures CabalSpecV3_0 = Set.fromList - [ Elif - , CommonStanzas - , Globstar - , MultipleLibraries - ] - -cabalSpecSupports :: CabalSpecVersion -> [Int] -> Bool -cabalSpecSupports CabalSpecOld v = v < [1,21] -cabalSpecSupports CabalSpecV1_22 v = v < [1,23] -cabalSpecSupports CabalSpecV1_24 v = v < [1,25] -cabalSpecSupports CabalSpecV2_0 v = v < [2,1] -cabalSpecSupports CabalSpecV2_2 v = v < [2,3] -cabalSpecSupports CabalSpecV2_4 _ = True -cabalSpecSupports CabalSpecV3_0 _ = True +cabalSpecFromVersionDigits :: [Int] -> CabalSpecVersion +cabalSpecFromVersionDigits v + | v >= [2,5] = CabalSpecV3_0 + | v >= [2,3] = CabalSpecV2_4 + | v >= [2,1] = CabalSpecV2_2 + | v >= [1,25] = CabalSpecV2_0 + | v >= [1,23] = CabalSpecV1_24 + | v >= [1,21] = CabalSpecV1_22 + | v >= [1,19] = CabalSpecV1_20 + | v >= [1,17] = CabalSpecV1_18 + | v >= [1,11] = CabalSpecV1_12 + | v >= [1,9] = CabalSpecV1_10 + | v >= [1,7] = CabalSpecV1_8 + | v >= [1,5] = CabalSpecV1_6 + | v >= [1,3] = CabalSpecV1_4 + | v >= [1,1] = CabalSpecV1_2 + | otherwise = CabalSpecV1_0 specHasCommonStanzas :: CabalSpecVersion -> HasCommonStanzas -specHasCommonStanzas CabalSpecV2_2 = HasCommonStanzas -specHasCommonStanzas CabalSpecV2_4 = HasCommonStanzas -specHasCommonStanzas CabalSpecV3_0 = HasCommonStanzas -specHasCommonStanzas _ = NoCommonStanzas +specHasCommonStanzas v = + if v >= CabalSpecV2_2 + then HasCommonStanzas + else NoCommonStanzas specHasElif :: CabalSpecVersion -> HasElif -specHasElif CabalSpecV2_2 = HasElif -specHasElif CabalSpecV2_4 = HasElif -specHasElif CabalSpecV3_0 = HasElif -specHasElif _ = NoElif - -------------------------------------------------------------------------------- --- Features -------------------------------------------------------------------------------- - -data CabalFeature - = Elif - | CommonStanzas - | Globstar - -- ^ Implemented in #5284. Not actually a change to the parser, - -- as filename patterns are opaque to it currently. - | MultipleLibraries - -- ^ Multiple public libraries in a package. Implemented in #5526. - deriving (Eq, Ord, Show, Read, Enum, Bounded, Typeable, Data, Generic) +specHasElif v = + if v >= CabalSpecV2_2 + then HasElif + else NoElif ------------------------------------------------------------------------------- -- Booleans ------------------------------------------------------------------------------- +-- IDEA: make some kind of tagged booleans? data HasElif = HasElif | NoElif deriving (Eq, Show) diff --git a/Cabal/Distribution/FieldGrammar.hs b/Cabal/Distribution/FieldGrammar.hs index 71a02d8ddbbd622f667a5c8dc81e457fba4019a2..9c89e74fc52cf7358d56da6409eda5a4535d9c52 100644 --- a/Cabal/Distribution/FieldGrammar.hs +++ b/Cabal/Distribution/FieldGrammar.hs @@ -9,7 +9,6 @@ module Distribution.FieldGrammar ( optionalField, optionalFieldDef, monoidalField, - deprecatedField', -- * Concrete grammar implementations ParsecFieldGrammar, ParsecFieldGrammar', diff --git a/Cabal/Distribution/FieldGrammar/Class.hs b/Cabal/Distribution/FieldGrammar/Class.hs index 6bd391dfe1719332fdf343e9a93148a2ce6a6d1c..9400e04085f7d84804bd1d3e26a222fdcdfc43b2 100644 --- a/Cabal/Distribution/FieldGrammar/Class.hs +++ b/Cabal/Distribution/FieldGrammar/Class.hs @@ -4,7 +4,6 @@ module Distribution.FieldGrammar.Class ( optionalField, optionalFieldDef, monoidalField, - deprecatedField', ) where import Distribution.Compat.Lens @@ -13,10 +12,11 @@ import Prelude () import Data.Functor.Identity (Identity (..)) -import Distribution.Compat.Newtype (Newtype) -import Distribution.Parsec.Class (Parsec) +import Distribution.CabalSpecVersion (CabalSpecVersion) +import Distribution.Compat.Newtype (Newtype) +import Distribution.Parsec.Class (Parsec) import Distribution.Parsec.Field -import Distribution.Pretty (Pretty) +import Distribution.Pretty (Pretty) -- | 'FieldGrammar' is parametrised by -- @@ -90,15 +90,15 @@ class FieldGrammar g where -- | Deprecated since deprecatedSince - :: [Int] -- ^ version - -> String -- ^ deprecation message + :: CabalSpecVersion -- ^ version + -> String -- ^ deprecation message -> g s a -> g s a -- | Annotate field with since spec-version. availableSince - :: [Int] -- ^ spec version - -> a -- ^ default value + :: CabalSpecVersion -- ^ spec version + -> a -- ^ default value -> g s a -> g s a @@ -134,14 +134,3 @@ monoidalField -> ALens' s a -- ^ lens into the field -> g s a monoidalField fn = monoidalFieldAla fn Identity - --- | Deprecated field. If found, warning is issued. --- --- /Note:/ also it's not pretty printed! --- -deprecatedField' - :: FieldGrammar g - => String -- ^ deprecation message - -> g s a - -> g s a -deprecatedField' = deprecatedSince [] diff --git a/Cabal/Distribution/FieldGrammar/Parsec.hs b/Cabal/Distribution/FieldGrammar/Parsec.hs index 916403f0741c6aa6c80c80f540ebeb8c6ac2b1f5..7ec44690ae4e7a16483bca92f52749c91b8b1a79 100644 --- a/Cabal/Distribution/FieldGrammar/Parsec.hs +++ b/Cabal/Distribution/FieldGrammar/Parsec.hs @@ -231,28 +231,29 @@ instance FieldGrammar ParsecFieldGrammar where availableSince vs def (ParsecFG names prefixes parser) = ParsecFG names prefixes parser' where parser' v values - | cabalSpecSupports v vs = parser v values + | v >= vs = parser v values | otherwise = do let unknownFields = Map.intersection values $ Map.fromSet (const ()) names for_ (Map.toList unknownFields) $ \(name, fields) -> for_ fields $ \(MkNamelessField pos _) -> parseWarning pos PWTUnknownField $ - "The field " <> show name <> " is available since Cabal " ++ show vs + "The field " <> show name <> " is available only since the Cabal specification version " ++ showCabalSpecVersion vs ++ "." pure def -- todo we know about this field - deprecatedSince (_ : _) _ grammar = grammar -- pass on non-empty version - deprecatedSince _ msg (ParsecFG names prefixes parser) = ParsecFG names prefixes parser' + deprecatedSince vs msg (ParsecFG names prefixes parser) = ParsecFG names prefixes parser' where - parser' v values = do - let deprecatedFields = Map.intersection values $ Map.fromSet (const ()) names - for_ (Map.toList deprecatedFields) $ \(name, fields) -> - for_ fields $ \(MkNamelessField pos _) -> - parseWarning pos PWTDeprecatedField $ - "The field " <> show name <> " is deprecated. " ++ msg - - parser v values + parser' v values + | v >= vs = do + let deprecatedFields = Map.intersection values $ Map.fromSet (const ()) names + for_ (Map.toList deprecatedFields) $ \(name, fields) -> + for_ fields $ \(MkNamelessField pos _) -> + parseWarning pos PWTDeprecatedField $ + "The field " <> show name <> " is deprecated in the Cabal specification version " ++ showCabalSpecVersion vs ++ ". " ++ msg + + parser v values + | otherwise = parser v values knownField fn = ParsecFG (Set.singleton fn) Set.empty (\_ _ -> pure ()) diff --git a/Cabal/Distribution/FieldGrammar/Pretty.hs b/Cabal/Distribution/FieldGrammar/Pretty.hs index d0f585c602d81b9dcf7c3adbd3b8bb89e9331a9c..e8a152525d5de0b45bbecf2ad125a58ec915fa31 100644 --- a/Cabal/Distribution/FieldGrammar/Pretty.hs +++ b/Cabal/Distribution/FieldGrammar/Pretty.hs @@ -74,7 +74,6 @@ instance FieldGrammar PrettyFieldGrammar where ] knownField _ = pure () - deprecatedSince [] _ _ = PrettyFG (\_ -> mempty) deprecatedSince _ _ x = x availableSince _ _ = id hiddenField _ = PrettyFG (\_ -> mempty) diff --git a/Cabal/Distribution/PackageDescription/FieldGrammar.hs b/Cabal/Distribution/PackageDescription/FieldGrammar.hs index f4178cc2f987f9bc3ef9be1109d5fae9e8e402c5..63a9fff875981820e602614cadc71706c290a3f7 100644 --- a/Cabal/Distribution/PackageDescription/FieldGrammar.hs +++ b/Cabal/Distribution/PackageDescription/FieldGrammar.hs @@ -43,6 +43,7 @@ import Distribution.Compat.Lens import Distribution.Compat.Prelude import Prelude () +import Distribution.CabalSpecVersion import Distribution.Compiler (CompilerFlavor (..)) import Distribution.FieldGrammar import Distribution.ModuleName (ModuleName) @@ -126,7 +127,7 @@ libraryFieldGrammar n = Library n <$> monoidalFieldAla "exposed-modules" (alaList' VCat MQuoted) L.exposedModules <*> monoidalFieldAla "reexported-modules" (alaList CommaVCat) L.reexportedModules <*> monoidalFieldAla "signatures" (alaList' VCat MQuoted) L.signatures - ^^^ availableSince [2,0] [] + ^^^ availableSince CabalSpecV2_0 [] <*> booleanFieldDef "exposed" L.libExposed True <*> blurFieldGrammar L.libBuildInfo buildInfoFieldGrammar {-# SPECIALIZE libraryFieldGrammar :: Maybe UnqualComponentName -> ParsecFieldGrammar' Library #-} @@ -160,7 +161,7 @@ executableFieldGrammar n = Executable n -- main-is is optional as conditional blocks don't have it <$> optionalFieldDefAla "main-is" FilePathNT L.modulePath "" <*> optionalFieldDef "scope" L.exeScope ExecutablePublic - ^^^ availableSince [2,0] ExecutablePublic + ^^^ availableSince CabalSpecV2_0 ExecutablePublic <*> blurFieldGrammar L.buildInfo buildInfoFieldGrammar {-# SPECIALIZE executableFieldGrammar :: UnqualComponentName -> ParsecFieldGrammar' Executable #-} {-# SPECIALIZE executableFieldGrammar :: UnqualComponentName -> PrettyFieldGrammar' Executable #-} @@ -365,7 +366,8 @@ buildInfoFieldGrammar buildInfoFieldGrammar = BuildInfo <$> booleanFieldDef "buildable" L.buildable True <*> monoidalFieldAla "build-tools" (alaList CommaFSep) L.buildTools - ^^^ deprecatedSince [2,0] "Please use 'build-tool-depends' field" + ^^^ deprecatedSince CabalSpecV2_0 + "Please use 'build-tool-depends' field" <*> monoidalFieldAla "build-tool-depends" (alaList CommaFSep) L.buildToolDepends -- {- ^^^ availableSince [2,0] [] -} -- here, we explicitly want to recognise build-tool-depends for all Cabal files @@ -377,7 +379,7 @@ buildInfoFieldGrammar = BuildInfo <*> monoidalFieldAla "cmm-options" (alaList' NoCommaFSep Token') L.cmmOptions <*> monoidalFieldAla "cc-options" (alaList' NoCommaFSep Token') L.ccOptions <*> monoidalFieldAla "cxx-options" (alaList' NoCommaFSep Token') L.cxxOptions - ^^^ availableSince [2,1] [] -- TODO change to 2,2 when version is bumped + ^^^ availableSince CabalSpecV2_2 [] <*> monoidalFieldAla "ld-options" (alaList' NoCommaFSep Token') L.ldOptions <*> monoidalFieldAla "pkgconfig-depends" (alaList CommaFSep) L.pkgconfigDepends <*> monoidalFieldAla "frameworks" (alaList' FSep Token) L.frameworks @@ -386,25 +388,26 @@ buildInfoFieldGrammar = BuildInfo <*> monoidalFieldAla "cmm-sources" (alaList' VCat FilePathNT) L.cmmSources <*> monoidalFieldAla "c-sources" (alaList' VCat FilePathNT) L.cSources <*> monoidalFieldAla "cxx-sources" (alaList' VCat FilePathNT) L.cxxSources - ^^^ availableSince [2,1] [] -- TODO change to 2,2 when version is bumped + ^^^ availableSince CabalSpecV2_2 [] <*> monoidalFieldAla "js-sources" (alaList' VCat FilePathNT) L.jsSources <*> hsSourceDirsGrammar <*> monoidalFieldAla "other-modules" (alaList' VCat MQuoted) L.otherModules <*> monoidalFieldAla "virtual-modules" (alaList' VCat MQuoted) L.virtualModules - ^^^ availableSince [2,1] [] -- TODO change to 2,2 when version is bumped + ^^^ availableSince CabalSpecV2_2 [] <*> monoidalFieldAla "autogen-modules" (alaList' VCat MQuoted) L.autogenModules <*> optionalFieldAla "default-language" MQuoted L.defaultLanguage <*> monoidalFieldAla "other-languages" (alaList' FSep MQuoted) L.otherLanguages <*> monoidalFieldAla "default-extensions" (alaList' FSep MQuoted) L.defaultExtensions <*> monoidalFieldAla "other-extensions" (alaList' FSep MQuoted) L.otherExtensions <*> monoidalFieldAla "extensions" (alaList' FSep MQuoted) L.oldExtensions - ^^^ deprecatedSince [1,12] "Please use 'default-extensions' or 'other-extensions' fields." + ^^^ deprecatedSince CabalSpecV1_12 + "Please use 'default-extensions' or 'other-extensions' fields." <*> monoidalFieldAla "extra-libraries" (alaList' VCat Token) L.extraLibs <*> monoidalFieldAla "extra-ghci-libraries" (alaList' VCat Token) L.extraGHCiLibs <*> monoidalFieldAla "extra-bundled-libraries" (alaList' VCat Token) L.extraBundledLibs <*> monoidalFieldAla "extra-library-flavours" (alaList' VCat Token) L.extraLibFlavours <*> monoidalFieldAla "extra-dynamic-library-flavours" (alaList' VCat Token) L.extraDynLibFlavours - ^^^ availableSince [2,5] [] -- TODO change to 3.0 when version is bumped + ^^^ availableSince CabalSpecV3_0 [] <*> monoidalFieldAla "extra-lib-dirs" (alaList' FSep FilePathNT) L.extraLibDirs <*> monoidalFieldAla "include-dirs" (alaList' FSep FilePathNT) L.includeDirs <*> monoidalFieldAla "includes" (alaList' FSep FilePathNT) L.includes @@ -416,7 +419,7 @@ buildInfoFieldGrammar = BuildInfo <*> prefixedFields "x-" L.customFieldsBI <*> monoidalFieldAla "build-depends" (alaList CommaVCat) L.targetBuildDepends <*> monoidalFieldAla "mixins" (alaList CommaVCat) L.mixins - ^^^ availableSince [2,0] [] + ^^^ availableSince CabalSpecV2_0 [] {-# SPECIALIZE buildInfoFieldGrammar :: ParsecFieldGrammar' BuildInfo #-} {-# SPECIALIZE buildInfoFieldGrammar :: PrettyFieldGrammar' BuildInfo #-} @@ -425,8 +428,13 @@ hsSourceDirsGrammar => g BuildInfo [FilePath] hsSourceDirsGrammar = (++) <$> monoidalFieldAla "hs-source-dirs" (alaList' FSep FilePathNT) L.hsSourceDirs - <*> monoidalFieldAla "hs-source-dir" (alaList' FSep FilePathNT) L.hsSourceDirs - ^^^ deprecatedField' "Please use 'hs-source-dirs'" + <*> monoidalFieldAla "hs-source-dir" (alaList' FSep FilePathNT) wrongLens + --- https://github.com/haskell/cabal/commit/49e3cdae3bdf21b017ccd42e66670ca402e22b44 + ^^^ deprecatedSince CabalSpecV1_2 "Please use 'hs-source-dirs'" + where + -- TODO: make pretty printer aware of CabalSpecVersion + wrongLens :: Functor f => LensLike' f BuildInfo [FilePath] + wrongLens f bi = (\fps -> set L.hsSourceDirs fps bi) <$> f [] optionsFieldGrammar :: (FieldGrammar g, Applicative (g BuildInfo)) diff --git a/Cabal/Distribution/PackageDescription/Parsec.hs b/Cabal/Distribution/PackageDescription/Parsec.hs index a3387eb9e5fea1ecef4e23271a9c83af6b10ba6c..7855e4d91f185ff5526b5fcb8efd091c7a97f886 100644 --- a/Cabal/Distribution/PackageDescription/Parsec.hs +++ b/Cabal/Distribution/PackageDescription/Parsec.hs @@ -173,14 +173,7 @@ parseGenericPackageDescription' cabalVerM lexWarnings utf8WarnPos fs = do return v - let specVer - | cabalVer >= mkVersion [2,5] = CabalSpecV3_0 - | cabalVer >= mkVersion [2,3] = CabalSpecV2_4 - | cabalVer >= mkVersion [2,1] = CabalSpecV2_2 - | cabalVer >= mkVersion [1,25] = CabalSpecV2_0 - | cabalVer >= mkVersion [1,23] = CabalSpecV1_24 - | cabalVer >= mkVersion [1,21] = CabalSpecV1_22 - | otherwise = CabalSpecOld + let specVer = cabalSpecFromVersionDigits (versionNumbers cabalVer) -- reset cabal version setCabalSpecVersion (Just cabalVer) diff --git a/Cabal/Distribution/Types/BuildType.hs b/Cabal/Distribution/Types/BuildType.hs index 90680ae2bc338a8063c96129d9ca1a030216fee0..3138e92b3c1db722aa6b93bda51ae8d4175ad6df 100644 --- a/Cabal/Distribution/Types/BuildType.hs +++ b/Cabal/Distribution/Types/BuildType.hs @@ -48,7 +48,7 @@ instance Parsec BuildType where "Make" -> return Make "Default" -> do v <- askCabalSpecVersion - if v <= CabalSpecOld + if v <= CabalSpecV1_18 -- oldest version needing this, based on hackage-tests then do parsecWarning PWTBuildTypeDefault "build-type: Default is parsed as Custom for legacy reasons. See https://github.com/haskell/cabal/issues/5020" return Custom diff --git a/Cabal/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs b/Cabal/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs index 9b3279cb142ba530eca2636da8c3851c1a0101e1..70cd84f555e2a20de78d21905cfda550d1c5e14b 100644 --- a/Cabal/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs +++ b/Cabal/Distribution/Types/InstalledPackageInfo/FieldGrammar.hs @@ -10,6 +10,7 @@ import Distribution.Compat.Prelude import Prelude () import Distribution.Backpack +import Distribution.CabalSpecVersion import Distribution.Compat.Lens (Lens', (&), (.~)) import Distribution.Compat.Newtype import Distribution.FieldGrammar @@ -56,7 +57,8 @@ ipiFieldGrammar ipiFieldGrammar = mkInstalledPackageInfo -- Deprecated fields <$> monoidalFieldAla "hugs-options" (alaList' FSep Token) unitedList - ^^^ deprecatedField' "hugs isn't supported anymore" + --- https://github.com/haskell/cabal/commit/40f3601e17024f07e0da8e64d3dd390177ce908b + ^^^ deprecatedSince CabalSpecV1_22 "hugs isn't supported anymore" -- Very basic fields: name, version, package-name and lib-name <+> blurFieldGrammar basic basicFieldGrammar -- Basic fields diff --git a/Cabal/tests/ParserTests/regressions/wl-pprint-indef.format b/Cabal/tests/ParserTests/regressions/wl-pprint-indef.format index 64a5c54c8e8af2ce941d6b4319201079f1fdd0e9..d0ad2f213f6830bbf9df5f91bc11aa60151e5db0 100644 --- a/Cabal/tests/ParserTests/regressions/wl-pprint-indef.format +++ b/Cabal/tests/ParserTests/regressions/wl-pprint-indef.format @@ -1,6 +1,6 @@ -wl-pprint-indef.cabal:28:3: The field "mixins" is available since Cabal [2,0] -wl-pprint-indef.cabal:27:3: The field "signatures" is available since Cabal [2,0] -wl-pprint-indef.cabal:23:3: The field "mixins" is available since Cabal [2,0] +wl-pprint-indef.cabal:28:3: The field "mixins" is available only since the Cabal specification version 2.0. +wl-pprint-indef.cabal:27:3: The field "signatures" is available only since the Cabal specification version 2.0. +wl-pprint-indef.cabal:23:3: The field "mixins" is available only since the Cabal specification version 2.0. cabal-version: >=1.6 name: wl-pprint-indef version: 1.2