Skip to content

Commit

Permalink
Tweak how 'allow-newer' looks like in the default config file.
Browse files Browse the repository at this point in the history
Before:

    allow-newer: False

After:

    -- allow-newer: False
  • Loading branch information
23Skidoo committed Feb 20, 2016
1 parent 67fc825 commit b428a2e
Show file tree
Hide file tree
Showing 6 changed files with 39 additions and 24 deletions.
4 changes: 3 additions & 1 deletion Cabal/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -315,7 +315,9 @@ configure (pkg_descr0', pbi) cfg = do
-- Ignore '--allow-newer' when we're given '--exact-configuration'.
if fromFlagOrDefault False (configExactConfiguration cfg)
then pkg_descr0'
else relaxPackageDeps (configAllowNewer cfg) pkg_descr0'
else relaxPackageDeps
(fromMaybe AllowNewerNone $ configAllowNewer cfg)
pkg_descr0'

setupMessage verbosity "Configuring" (packageId pkg_descr0)

Expand Down
23 changes: 12 additions & 11 deletions Cabal/Distribution/Simple/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -308,19 +308,19 @@ isAllowNewer AllowNewerNone = False
isAllowNewer (AllowNewerSome _) = True
isAllowNewer AllowNewerAll = True

allowNewerParser :: ReadE AllowNewer
allowNewerParser :: ReadE (Maybe AllowNewer)
allowNewerParser = ReadE $ \s ->
case readPToMaybe pkgsParser s of
Just pkgs -> Right . AllowNewerSome $ pkgs
Just pkgs -> Right . Just . AllowNewerSome $ pkgs
Nothing -> Left ("Cannot parse the list of packages: " ++ s)
where
pkgsParser = Parse.sepBy1 parse (Parse.char ',')

allowNewerPrinter :: AllowNewer -> [Maybe String]
allowNewerPrinter AllowNewerNone = []
allowNewerPrinter AllowNewerAll = [Nothing]
allowNewerPrinter (AllowNewerSome pkgs) =
[Just . intercalate "," . map display $ pkgs]
allowNewerPrinter :: (Maybe AllowNewer) -> [Maybe String]
allowNewerPrinter Nothing = []
allowNewerPrinter (Just AllowNewerNone) = []
allowNewerPrinter (Just AllowNewerAll) = [Nothing]
allowNewerPrinter (Just (AllowNewerSome pkgs)) = map (Just . display) $ pkgs

-- | Flags to @configure@ command.
--
Expand Down Expand Up @@ -392,8 +392,9 @@ data ConfigFlags = ConfigFlags {
-- ^Halt and show an error message indicating an error in flag assignment
configRelocatable :: Flag Bool, -- ^ Enable relocatable package built
configDebugInfo :: Flag DebugInfoLevel, -- ^ Emit debug info.
configAllowNewer :: AllowNewer -- ^ Ignore upper bounds on all or some
-- dependencies.
configAllowNewer :: Maybe AllowNewer
-- ^ Ignore upper bounds on all or some dependencies. Wrapped in 'Maybe' to
-- distinguish between "default" and "explicitly disabled".
}
deriving (Generic, Read, Show)

Expand Down Expand Up @@ -440,7 +441,7 @@ defaultConfigFlags progConf = emptyConfigFlags {
configFlagError = NoFlag,
configRelocatable = Flag False,
configDebugInfo = Flag NoDebugInfo,
configAllowNewer = AllowNewerNone
configAllowNewer = Nothing
}

configureCommand :: ProgramConfiguration -> CommandUI ConfigFlags
Expand Down Expand Up @@ -686,7 +687,7 @@ configureOptions showOrParseArgs =
,option [] ["allow-newer"]
("Ignore upper bounds in all dependencies or DEPS")
configAllowNewer (\v flags -> flags { configAllowNewer = v})
(optArg "DEPS" allowNewerParser AllowNewerAll allowNewerPrinter)
(optArg "DEPS" allowNewerParser (Just AllowNewerAll) allowNewerPrinter)

,option "" ["exact-configuration"]
"All direct dependencies and flags are provided on the command line."
Expand Down
22 changes: 15 additions & 7 deletions cabal-install/Distribution/Client/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ import Distribution.Simple.Compiler
( DebugInfoLevel(..), OptimisationLevel(..) )
import Distribution.Simple.Setup
( ConfigFlags(..), configureOptions, defaultConfigFlags
, AllowNewer(..), isAllowNewer
, AllowNewer(..)
, HaddockFlags(..), haddockOptions, defaultHaddockFlags
, installDirsOptions, optionDistPref
, programConfigurationPaths', programConfigurationOptions
Expand All @@ -75,7 +75,7 @@ import Distribution.ParseUtils
, ParseResult(..), PError(..), PWarning(..)
, locatedErrorMsg, showPWarning
, readFields, warning, lineNo
, simpleField, boolField, listField, spaceListField
, simpleField, listField, spaceListField
, parseFilePathQ, parseTokenQ )
import Distribution.Client.ParseUtils
( parseFields, ppFields, ppSection )
Expand Down Expand Up @@ -640,7 +640,8 @@ commentSavedConfig = do
savedInstallFlags = defaultInstallFlags,
savedConfigureExFlags = defaultConfigExFlags,
savedConfigureFlags = (defaultConfigFlags defaultProgramConfiguration) {
configUserInstall = toFlag defaultUserInstall
configUserInstall = toFlag defaultUserInstall,
configAllowNewer = Just AllowNewerNone
},
savedUserInstallDirs = fmap toFlag userInstallDirs,
savedGlobalInstallDirs = fmap toFlag globalInstallDirs,
Expand Down Expand Up @@ -669,10 +670,17 @@ configFieldDescriptions src =
[simpleField "compiler"
(fromFlagOrDefault Disp.empty . fmap Text.disp) (optional Text.parse)
configHcFlavor (\v flags -> flags { configHcFlavor = v })
,let toAllowNewer True = AllowNewerAll
toAllowNewer False = AllowNewerNone in
boolField "allow-newer" (isAllowNewer . configAllowNewer)
(\v flags -> flags { configAllowNewer = toAllowNewer v })
,let showAllowNewer Nothing = mempty
showAllowNewer (Just AllowNewerNone) = Disp.text "False"
showAllowNewer (Just _) = Disp.text "True"

toAllowNewer True = Just AllowNewerAll
toAllowNewer False = Just AllowNewerNone

parseAllowNewer = toAllowNewer `fmap` Text.parse in
simpleField "allow-newer"
showAllowNewer parseAllowNewer
configAllowNewer (\v flags -> flags { configAllowNewer = v })
-- TODO: The following is a temporary fix. The "optimization"
-- and "debug-info" fields are OptArg, and viewAsFieldDescr
-- fails on that. Instead of a hand-written hackaged parser
Expand Down
9 changes: 6 additions & 3 deletions cabal-install/Distribution/Client/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,8 @@ import Distribution.Simple.Compiler
( Compiler, CompilerInfo, compilerInfo, PackageDB(..), PackageDBStack )
import Distribution.Simple.Program (ProgramConfiguration )
import Distribution.Simple.Setup
( ConfigFlags(..), fromFlag, toFlag, flagToMaybe, fromFlagOrDefault )
( ConfigFlags(..), AllowNewer(..)
, fromFlag, toFlag, flagToMaybe, fromFlagOrDefault )
import Distribution.Simple.PackageIndex
( InstalledPackageIndex, lookupPackageName )
import Distribution.Simple.Utils
Expand Down Expand Up @@ -86,7 +87,8 @@ chooseCabalVersion configFlags maybeVersion =
where
-- Cabal < 1.19.2 doesn't support '--exact-configuration' which is needed
-- for '--allow-newer' to work.
allowNewer = isAllowNewer (configAllowNewer configFlags)
allowNewer = isAllowNewer
(fromMaybe AllowNewerNone $ configAllowNewer configFlags)

defaultVersionRange = if allowNewer
then orLaterVersion (Version [1,19,2] [])
Expand Down Expand Up @@ -288,7 +290,8 @@ planLocalPackage verbosity comp platform configFlags configExFlags
fromFlagOrDefault False $ configBenchmarks configFlags

resolverParams =
removeUpperBounds (configAllowNewer configFlags)
removeUpperBounds
(fromMaybe AllowNewerNone $ configAllowNewer configFlags)

. addPreferences
-- preferences from the config file or command line
Expand Down
3 changes: 2 additions & 1 deletion cabal-install/Distribution/Client/Install.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,7 @@ import qualified Distribution.Simple.Configure as Configure
import Distribution.Simple.Setup
( haddockCommand, HaddockFlags(..)
, buildCommand, BuildFlags(..), emptyBuildFlags
, AllowNewer(..)
, toFlag, fromFlag, fromFlagOrDefault, flagToMaybe, defaultDistPref )
import qualified Distribution.Simple.Setup as Cabal
( Flag(..)
Expand Down Expand Up @@ -417,7 +418,7 @@ planPackages comp platform mSandboxPkgInfo solver
maxBackjumps = fromFlag (installMaxBackjumps installFlags)
upgradeDeps = fromFlag (installUpgradeDeps installFlags)
onlyDeps = fromFlag (installOnlyDeps installFlags)
allowNewer = (configAllowNewer configFlags)
allowNewer = fromMaybe AllowNewerNone (configAllowNewer configFlags)

-- | Remove the provided targets from the install plan.
pruneInstallPlan :: Package targetpkg
Expand Down
2 changes: 1 addition & 1 deletion cabal-install/Distribution/Client/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -370,7 +370,7 @@ filterConfigureFlags flags cabalLibVersion
configConstraints = [],
-- Passing '--allow-newer' to Setup.hs is unnecessary, we use
-- '--exact-configuration' instead.
configAllowNewer = Cabal.AllowNewerNone
configAllowNewer = Just Cabal.AllowNewerNone
}

-- Cabal < 1.23 doesn't know about '--profiling-detail'.
Expand Down

0 comments on commit b428a2e

Please sign in to comment.