never executed always true always false
    1 {-# LANGUAGE ScopedTypeVariables #-}
    2 {-# LANGUAGE RecordWildCards     #-}
    3 {-# LANGUAGE RankNTypes          #-}
    4 {-# LANGUAGE DeriveGeneric       #-}
    5 {-# LANGUAGE LambdaCase          #-}
    6 -----------------------------------------------------------------------------
    7 -- |
    8 -- Module      :  Distribution.Client.Setup
    9 -- Copyright   :  (c) David Himmelstrup 2005
   10 -- License     :  BSD-like
   11 --
   12 -- Maintainer  :  lemmih@gmail.com
   13 -- Stability   :  provisional
   14 -- Portability :  portable
   15 --
   16 --
   17 -----------------------------------------------------------------------------
   18 module Distribution.Client.Setup
   19     ( globalCommand, GlobalFlags(..), defaultGlobalFlags
   20     , RepoContext(..), withRepoContext
   21     , configureCommand, ConfigFlags(..), configureOptions, filterConfigureFlags
   22     , configPackageDB', configCompilerAux'
   23     , configureExCommand, ConfigExFlags(..), defaultConfigExFlags
   24     , buildCommand, BuildFlags(..)
   25     , filterTestFlags
   26     , replCommand, testCommand, benchmarkCommand, testOptions, benchmarkOptions
   27                         , configureExOptions, reconfigureCommand
   28     , installCommand, InstallFlags(..), installOptions, defaultInstallFlags
   29     , filterHaddockArgs, filterHaddockFlags, haddockOptions
   30     , defaultSolver, defaultMaxBackjumps
   31     , listCommand, ListFlags(..), listNeedsCompiler
   32     ,UpdateFlags(..), defaultUpdateFlags
   33     , infoCommand, InfoFlags(..)
   34     , fetchCommand, FetchFlags(..)
   35     , freezeCommand, FreezeFlags(..)
   36     , genBoundsCommand
   37     , outdatedCommand, OutdatedFlags(..), IgnoreMajorVersionBumps(..)
   38     , getCommand, unpackCommand, GetFlags(..)
   39     , checkCommand
   40     , formatCommand
   41     , uploadCommand, UploadFlags(..), IsCandidate(..)
   42     , reportCommand, ReportFlags(..)
   43     , runCommand
   44     , initCommand, initOptions, IT.InitFlags(..)
   45     , actAsSetupCommand, ActAsSetupFlags(..)
   46     , userConfigCommand, UserConfigFlags(..)
   47     , manpageCommand
   48     , haddockCommand
   49     , cleanCommand
   50     , copyCommand
   51     , registerCommand
   52 
   53     , liftOptions
   54     , yesNoOpt
   55     ) where
   56 
   57 import Prelude ()
   58 import Distribution.Client.Compat.Prelude hiding (get)
   59 
   60 import Distribution.Client.Types.Credentials (Username (..), Password (..))
   61 import Distribution.Client.Types.Repo (RemoteRepo(..), LocalRepo (..))
   62 import Distribution.Client.Types.AllowNewer (AllowNewer(..), AllowOlder(..), RelaxDeps(..))
   63 import Distribution.Client.Types.WriteGhcEnvironmentFilesPolicy
   64 
   65 import Distribution.Client.BuildReports.Types
   66          ( ReportLevel(..) )
   67 import Distribution.Client.Dependency.Types
   68          ( PreSolver(..) )
   69 import Distribution.Client.IndexUtils.ActiveRepos
   70          ( ActiveRepos )
   71 import Distribution.Client.IndexUtils.IndexState
   72          ( TotalIndexState, headTotalIndexState )
   73 import qualified Distribution.Client.Init.Types as IT
   74          ( InitFlags(..), PackageType(..), defaultInitFlags )
   75 import Distribution.Client.Targets
   76          ( UserConstraint, readUserConstraint )
   77 import Distribution.Utils.NubList
   78          ( NubList, toNubList, fromNubList)
   79 
   80 import Distribution.Solver.Types.ConstraintSource
   81 import Distribution.Solver.Types.Settings
   82 
   83 import Distribution.Simple.Compiler ( Compiler, PackageDB, PackageDBStack )
   84 import Distribution.Simple.Program (ProgramDb, defaultProgramDb)
   85 import Distribution.Simple.Command hiding (boolOpt, boolOpt')
   86 import qualified Distribution.Simple.Command as Command
   87 import Distribution.Simple.Configure
   88        ( configCompilerAuxEx, interpretPackageDbFlags, computeEffectiveProfiling )
   89 import qualified Distribution.Simple.Setup as Cabal
   90 import Distribution.Simple.Flag
   91          ( Flag(..), toFlag, flagToMaybe, flagToList, maybeToFlag
   92          , flagElim, fromFlagOrDefault
   93          )
   94 import Distribution.Simple.Setup
   95          ( ConfigFlags(..), BuildFlags(..), ReplFlags
   96          , TestFlags, BenchmarkFlags
   97          , HaddockFlags(..)
   98          , CleanFlags(..)
   99          , CopyFlags(..), RegisterFlags(..)
  100          , readPackageDbList, showPackageDbList
  101          , BooleanFlag(..), optionVerbosity
  102          , boolOpt, boolOpt', trueArg, falseArg
  103          , optionNumJobs )
  104 import Distribution.Simple.InstallDirs
  105          ( PathTemplate, InstallDirs(..)
  106          , toPathTemplate, fromPathTemplate, combinePathTemplate )
  107 import Distribution.Version
  108          ( Version, mkVersion )
  109 import Distribution.Package
  110          ( PackageName )
  111 import Distribution.Types.GivenComponent
  112          ( GivenComponent(..) )
  113 import Distribution.Types.PackageVersionConstraint
  114          ( PackageVersionConstraint(..) )
  115 import Distribution.Types.UnqualComponentName
  116          ( unqualComponentNameToPackageName )
  117 import Distribution.PackageDescription
  118          ( BuildType(..), RepoKind(..), LibraryName(..) )
  119 import Distribution.System ( Platform )
  120 import Distribution.ReadE
  121          ( ReadE(..), succeedReadE, parsecToReadE )
  122 import qualified Distribution.Compat.CharParsing as P
  123 import Distribution.Verbosity
  124          ( lessVerbose, normal, verboseNoFlags, verboseNoTimestamp )
  125 import Distribution.Simple.Utils
  126          ( wrapText )
  127 import Distribution.Client.GlobalFlags
  128          ( GlobalFlags(..), defaultGlobalFlags
  129          , RepoContext(..), withRepoContext
  130          )
  131 import Distribution.Client.ManpageFlags (ManpageFlags, defaultManpageFlags, manpageOptions)
  132 import Distribution.FieldGrammar.Newtypes (SpecVersion (..))
  133 
  134 import Data.List
  135          ( deleteFirstsBy )
  136 import System.FilePath
  137          ( (</>) )
  138 
  139 globalCommand :: [Command action] -> CommandUI GlobalFlags
  140 globalCommand commands = CommandUI {
  141     commandName         = "",
  142     commandSynopsis     =
  143          "Command line interface to the Haskell Cabal infrastructure.",
  144     commandUsage        = \pname ->
  145          "See http://www.haskell.org/cabal/ for more information.\n"
  146       ++ "\n"
  147       ++ "Usage: " ++ pname ++ " [GLOBAL FLAGS] [COMMAND [FLAGS]]\n",
  148     commandDescription  = Just $ \pname ->
  149       let
  150         commands' = commands ++ [commandAddAction helpCommandUI undefined]
  151         cmdDescs = getNormalCommandDescriptions commands'
  152         -- if new commands are added, we want them to appear even if they
  153         -- are not included in the custom listing below. Thus, we calculate
  154         -- the `otherCmds` list and append it under the `other` category.
  155         -- Alternatively, a new testcase could be added that ensures that
  156         -- the set of commands listed here is equal to the set of commands
  157         -- that are actually available.
  158         otherCmds = deleteFirstsBy (==) (map fst cmdDescs)
  159           [ "help"
  160           , "update"
  161           , "install"
  162           , "fetch"
  163           , "list"
  164           , "info"
  165           , "user-config"
  166           , "get"
  167           , "init"
  168           , "configure"
  169           , "build"
  170           , "clean"
  171           , "run"
  172           , "repl"
  173           , "test"
  174           , "bench"
  175           , "check"
  176           , "sdist"
  177           , "upload"
  178           , "report"
  179           , "freeze"
  180           , "gen-bounds"
  181           , "outdated"
  182           , "haddock"
  183           , "hscolour"
  184           , "exec"
  185           , "new-build"
  186           , "new-configure"
  187           , "new-repl"
  188           , "new-freeze"
  189           , "new-run"
  190           , "new-test"
  191           , "new-bench"
  192           , "new-haddock"
  193           , "new-exec"
  194           , "new-update"
  195           , "new-install"
  196           , "new-clean"
  197           , "new-sdist"
  198           , "list-bin"
  199           -- v1 commands, stateful style
  200           , "v1-build"
  201           , "v1-configure"
  202           , "v1-repl"
  203           , "v1-freeze"
  204           , "v1-run"
  205           , "v1-test"
  206           , "v1-bench"
  207           , "v1-haddock"
  208           , "v1-exec"
  209           , "v1-update"
  210           , "v1-install"
  211           , "v1-clean"
  212           , "v1-sdist"
  213           , "v1-doctest"
  214           , "v1-copy"
  215           , "v1-register"
  216           , "v1-reconfigure"
  217           -- v2 commands, nix-style
  218           , "v2-build"
  219           , "v2-configure"
  220           , "v2-repl"
  221           , "v2-freeze"
  222           , "v2-run"
  223           , "v2-test"
  224           , "v2-bench"
  225           , "v2-haddock"
  226           , "v2-exec"
  227           , "v2-update"
  228           , "v2-install"
  229           , "v2-clean"
  230           , "v2-sdist"
  231           ]
  232         maxlen    = maximum $ [length name | (name, _) <- cmdDescs]
  233         align str = str ++ replicate (maxlen - length str) ' '
  234         startGroup n = " ["++n++"]"
  235         par          = ""
  236         addCmd n     = case lookup n cmdDescs of
  237                          Nothing -> ""
  238                          Just d -> "  " ++ align n ++ "    " ++ d
  239       in
  240          "Commands:\n"
  241       ++ unlines (
  242         [ startGroup "global"
  243         , addCmd "update"
  244         , addCmd "install"
  245         , par
  246         , addCmd "help"
  247         , addCmd "info"
  248         , addCmd "list"
  249         , addCmd "fetch"
  250         , addCmd "user-config"
  251         , par
  252         , startGroup "package"
  253         , addCmd "get"
  254         , addCmd "init"
  255         , par
  256         , addCmd "configure"
  257         , addCmd "build"
  258         , addCmd "clean"
  259         , par
  260         , addCmd "run"
  261         , addCmd "repl"
  262         , addCmd "test"
  263         , addCmd "bench"
  264         , par
  265         , addCmd "check"
  266         , addCmd "sdist"
  267         , addCmd "upload"
  268         , addCmd "report"
  269         , par
  270         , addCmd "freeze"
  271         , addCmd "gen-bounds"
  272         , addCmd "outdated"
  273         , addCmd "haddock"
  274         , addCmd "hscolour"
  275         , addCmd "exec"
  276         , addCmd "list-bin"
  277         , par
  278         , startGroup "new-style projects (forwards-compatible aliases)"
  279         , addCmd "v2-build"
  280         , addCmd "v2-configure"
  281         , addCmd "v2-repl"
  282         , addCmd "v2-run"
  283         , addCmd "v2-test"
  284         , addCmd "v2-bench"
  285         , addCmd "v2-freeze"
  286         , addCmd "v2-haddock"
  287         , addCmd "v2-exec"
  288         , addCmd "v2-update"
  289         , addCmd "v2-install"
  290         , addCmd "v2-clean"
  291         , addCmd "v2-sdist"
  292         , par
  293         , startGroup "legacy command aliases"
  294         , addCmd "v1-build"
  295         , addCmd "v1-configure"
  296         , addCmd "v1-repl"
  297         , addCmd "v1-run"
  298         , addCmd "v1-test"
  299         , addCmd "v1-bench"
  300         , addCmd "v1-freeze"
  301         , addCmd "v1-haddock"
  302         , addCmd "v1-exec"
  303         , addCmd "v1-update"
  304         , addCmd "v1-install"
  305         , addCmd "v1-clean"
  306         , addCmd "v1-sdist"
  307         , addCmd "v1-doctest"
  308         , addCmd "v1-copy"
  309         , addCmd "v1-register"
  310         , addCmd "v1-reconfigure"
  311         ] ++ if null otherCmds then [] else par
  312                                            :startGroup "other"
  313                                            :[addCmd n | n <- otherCmds])
  314       ++ "\n"
  315       ++ "For more information about a command use:\n"
  316       ++ "   " ++ pname ++ " COMMAND --help\n"
  317       ++ "or " ++ pname ++ " help COMMAND\n"
  318       ++ "\n"
  319       ++ "To install Cabal packages from hackage use:\n"
  320       ++ "  " ++ pname ++ " install foo [--dry-run]\n"
  321       ++ "\n"
  322       ++ "Occasionally you need to update the list of available packages:\n"
  323       ++ "  " ++ pname ++ " update\n",
  324     commandNotes = Nothing,
  325     commandDefaultFlags = mempty,
  326     commandOptions = args
  327   }
  328   where
  329     args :: ShowOrParseArgs -> [OptionField GlobalFlags]
  330     args ShowArgs  = argsShown
  331     args ParseArgs = argsShown ++ argsNotShown
  332 
  333     -- arguments we want to show in the help
  334     argsShown :: [OptionField GlobalFlags]
  335     argsShown = [
  336        option ['V'] ["version"]
  337          "Print version information"
  338          globalVersion (\v flags -> flags { globalVersion = v })
  339          trueArg
  340 
  341       ,option [] ["numeric-version"]
  342          "Print just the version number"
  343          globalNumericVersion (\v flags -> flags { globalNumericVersion = v })
  344          trueArg
  345 
  346       ,option [] ["config-file"]
  347          "Set an alternate location for the config file"
  348          globalConfigFile (\v flags -> flags { globalConfigFile = v })
  349          (reqArgFlag "FILE")
  350 
  351       ,option [] ["default-user-config"]
  352          "Set a location for a cabal.config file for projects without their own cabal.config freeze file."
  353          globalConstraintsFile (\v flags -> flags {globalConstraintsFile = v})
  354          (reqArgFlag "FILE")
  355 
  356       ,option [] ["ignore-expiry"]
  357          "Ignore expiry dates on signed metadata (use only in exceptional circumstances)"
  358          globalIgnoreExpiry (\v flags -> flags { globalIgnoreExpiry = v })
  359          trueArg
  360 
  361       ,option [] ["http-transport"]
  362          "Set a transport for http(s) requests. Accepts 'curl', 'wget', 'powershell', and 'plain-http'. (default: 'curl')"
  363          globalHttpTransport (\v flags -> flags { globalHttpTransport = v })
  364          (reqArgFlag "HttpTransport")
  365       ,option [] ["nix"]
  366          "Nix integration: run commands through nix-shell if a 'shell.nix' file exists"
  367          globalNix (\v flags -> flags { globalNix = v })
  368          (boolOpt [] [])
  369 
  370       ]
  371 
  372     -- arguments we don't want shown in the help
  373     argsNotShown :: [OptionField GlobalFlags]
  374     argsNotShown = [
  375        option [] ["remote-repo"]
  376          "The name and url for a remote repository"
  377          globalRemoteRepos (\v flags -> flags { globalRemoteRepos = v })
  378          (reqArg' "NAME:URL" (toNubList . maybeToList . readRemoteRepo) (map showRemoteRepo . fromNubList))
  379 
  380       ,option [] ["local-no-index-repo"]
  381          "The name and a path for a local no-index repository"
  382          globalLocalNoIndexRepos (\v flags -> flags { globalLocalNoIndexRepos = v })
  383          (reqArg' "NAME:PATH" (toNubList . maybeToList . readLocalRepo) (map showLocalRepo . fromNubList))
  384 
  385       ,option [] ["remote-repo-cache"]
  386          "The location where downloads from all remote repos are cached"
  387          globalCacheDir (\v flags -> flags { globalCacheDir = v })
  388          (reqArgFlag "DIR")
  389 
  390       ,option [] ["logs-dir", "logsdir"]
  391          "The location to put log files"
  392          globalLogsDir (\v flags -> flags { globalLogsDir = v })
  393          (reqArgFlag "DIR")
  394 
  395       ,option [] ["world-file"]
  396          "The location of the world file"
  397          globalWorldFile (\v flags -> flags { globalWorldFile = v })
  398          (reqArgFlag "FILE")
  399 
  400       ,option [] ["store-dir", "storedir"]
  401          "The location of the nix-local-build store"
  402          globalStoreDir (\v flags -> flags { globalStoreDir = v })
  403          (reqArgFlag "DIR")
  404 
  405       , option [] ["active-repositories"]
  406          "The active package repositories"
  407          globalActiveRepos (\v flags ->  flags { globalActiveRepos = v })
  408          (reqArg "REPOS" (parsecToReadE (\err -> "Error parsing active-repositories: " ++ err)
  409                                         (toFlag `fmap` parsec))
  410                          (map prettyShow . flagToList))
  411       ]
  412 
  413 -- ------------------------------------------------------------
  414 -- * Config flags
  415 -- ------------------------------------------------------------
  416 
  417 configureCommand :: CommandUI ConfigFlags
  418 configureCommand = c
  419   { commandName         = "configure"
  420   , commandDefaultFlags = mempty
  421   , commandDescription  = Just $ \_ -> wrapText $
  422          "Configure how the package is built by setting "
  423       ++ "package (and other) flags.\n"
  424       ++ "\n"
  425       ++ "The configuration affects several other commands, "
  426       ++ "including v1-build, v1-test, v1-bench, v1-run, v1-repl.\n"
  427   , commandUsage        = \pname ->
  428     "Usage: " ++ pname ++ " v1-configure [FLAGS]\n"
  429   , commandNotes = Just $ \pname ->
  430     (Cabal.programFlagsDescription defaultProgramDb ++ "\n")
  431       ++ "Examples:\n"
  432       ++ "  " ++ pname ++ " v1-configure\n"
  433       ++ "    Configure with defaults;\n"
  434       ++ "  " ++ pname ++ " v1-configure --enable-tests -fcustomflag\n"
  435       ++ "    Configure building package including tests,\n"
  436       ++ "    with some package-specific flag.\n"
  437   }
  438  where
  439   c = Cabal.configureCommand defaultProgramDb
  440 
  441 configureOptions ::  ShowOrParseArgs -> [OptionField ConfigFlags]
  442 configureOptions = commandOptions configureCommand
  443 
  444 -- | Given some 'ConfigFlags' for the version of Cabal that
  445 -- cabal-install was built with, and a target older 'Version' of
  446 -- Cabal that we want to pass these flags to, convert the
  447 -- flags into a form that will be accepted by the older
  448 -- Setup script.  Generally speaking, this just means filtering
  449 -- out flags that the old Cabal library doesn't understand, but
  450 -- in some cases it may also mean "emulating" a feature using
  451 -- some more legacy flags.
  452 filterConfigureFlags :: ConfigFlags -> Version -> ConfigFlags
  453 filterConfigureFlags flags cabalLibVersion
  454   -- NB: we expect the latest version to be the most common case,
  455   -- so test it first.
  456   | cabalLibVersion >= mkVersion [2,5,0]  = flags_latest
  457   -- The naming convention is that flags_version gives flags with
  458   -- all flags *introduced* in version eliminated.
  459   -- It is NOT the latest version of Cabal library that
  460   -- these flags work for; version of introduction is a more
  461   -- natural metric.
  462   | cabalLibVersion < mkVersion [1,3,10] = flags_1_3_10
  463   | cabalLibVersion < mkVersion [1,10,0] = flags_1_10_0
  464   | cabalLibVersion < mkVersion [1,12,0] = flags_1_12_0
  465   | cabalLibVersion < mkVersion [1,14,0] = flags_1_14_0
  466   | cabalLibVersion < mkVersion [1,18,0] = flags_1_18_0
  467   | cabalLibVersion < mkVersion [1,19,1] = flags_1_19_1
  468   | cabalLibVersion < mkVersion [1,19,2] = flags_1_19_2
  469   | cabalLibVersion < mkVersion [1,21,1] = flags_1_21_1
  470   | cabalLibVersion < mkVersion [1,22,0] = flags_1_22_0
  471   | cabalLibVersion < mkVersion [1,22,1] = flags_1_22_1
  472   | cabalLibVersion < mkVersion [1,23,0] = flags_1_23_0
  473   | cabalLibVersion < mkVersion [1,25,0] = flags_1_25_0
  474   | cabalLibVersion < mkVersion [2,1,0]  = flags_2_1_0
  475   | cabalLibVersion < mkVersion [2,5,0]  = flags_2_5_0
  476   | otherwise = error "the impossible just happened" -- see first guard
  477   where
  478     flags_latest = flags        {
  479       -- Cabal >= 1.19.1 uses '--dependency' and does not need '--constraint'.
  480       -- Note: this is not in the wrong place. configConstraints gets
  481       -- repopulated in flags_1_19_1 but it needs to be set to empty for
  482       -- newer versions first.
  483       configConstraints = []
  484       }
  485 
  486     flags_2_5_0 = flags_latest {
  487       -- Cabal < 2.5 does not understand --dependency=pkg:component=cid
  488       -- (public sublibraries), so we convert it to the legacy
  489       -- --dependency=pkg_or_internal_compoent=cid
  490         configDependencies =
  491           let convertToLegacyInternalDep (GivenComponent _ (LSubLibName cn) cid) =
  492                 Just $ GivenComponent
  493                        (unqualComponentNameToPackageName cn)
  494                        LMainLibName
  495                        cid
  496               convertToLegacyInternalDep (GivenComponent pn LMainLibName cid) =
  497                 Just $ GivenComponent pn LMainLibName cid
  498           in catMaybes $ convertToLegacyInternalDep <$> configDependencies flags
  499         -- Cabal < 2.5 doesn't know about '--allow-depending-on-private-libs'.
  500       , configAllowDependingOnPrivateLibs = NoFlag
  501         -- Cabal < 2.5 doesn't know about '--enable/disable-executable-static'.
  502       , configFullyStaticExe = NoFlag
  503       }
  504 
  505     flags_2_1_0 = flags_2_5_0 {
  506       -- Cabal < 2.1 doesn't know about -v +timestamp modifier
  507         configVerbosity   = fmap verboseNoTimestamp (configVerbosity flags_latest)
  508       -- Cabal < 2.1 doesn't know about --<enable|disable>-static
  509       , configStaticLib   = NoFlag
  510       , configSplitSections = NoFlag
  511       }
  512 
  513     flags_1_25_0 = flags_2_1_0 {
  514       -- Cabal < 1.25.0 doesn't know about --dynlibdir.
  515       configInstallDirs = configInstallDirs_1_25_0,
  516       -- Cabal < 1.25 doesn't have extended verbosity syntax
  517       configVerbosity   = fmap verboseNoFlags (configVerbosity flags_2_1_0),
  518       -- Cabal < 1.25 doesn't support --deterministic
  519       configDeterministic = mempty
  520       }
  521     configInstallDirs_1_25_0 = let dirs = configInstallDirs flags in
  522         dirs { dynlibdir = NoFlag
  523              , libexecsubdir = NoFlag
  524              , libexecdir = maybeToFlag $
  525                  combinePathTemplate <$> flagToMaybe (libexecdir dirs)
  526                                      <*> flagToMaybe (libexecsubdir dirs)
  527              }
  528     -- Cabal < 1.23 doesn't know about '--profiling-detail'.
  529     -- Cabal < 1.23 has a hacked up version of 'enable-profiling'
  530     -- which we shouldn't use.
  531     (tryLibProfiling, tryExeProfiling) = computeEffectiveProfiling flags
  532     flags_1_23_0 = flags_1_25_0 { configProfDetail    = NoFlag
  533                                 , configProfLibDetail = NoFlag
  534                                 , configIPID          = NoFlag
  535                                 , configProf          = NoFlag
  536                                 , configProfExe       = Flag tryExeProfiling
  537                                 , configProfLib       = Flag tryLibProfiling
  538                                 }
  539 
  540     -- Cabal == 1.22.0.* had a discontinuity (see #5946 or e9a8d48a3adce34d)
  541     -- due to temporary amnesia of the --*-executable-profiling flags
  542     flags_1_22_1 = flags_1_23_0 { configDebugInfo = NoFlag
  543                                 , configProfExe   = NoFlag
  544                                 }
  545 
  546     -- Cabal < 1.22 doesn't know about '--disable-debug-info'.
  547     flags_1_22_0 = flags_1_23_0 { configDebugInfo = NoFlag }
  548 
  549     -- Cabal < 1.21.1 doesn't know about 'disable-relocatable'
  550     -- Cabal < 1.21.1 doesn't know about 'enable-profiling'
  551     -- (but we already dealt with it in flags_1_23_0)
  552     flags_1_21_1 =
  553       flags_1_22_0 { configRelocatable = NoFlag
  554                    , configCoverage = NoFlag
  555                    , configLibCoverage = configCoverage flags
  556                    }
  557     -- Cabal < 1.19.2 doesn't know about '--exact-configuration' and
  558     -- '--enable-library-stripping'.
  559     flags_1_19_2 = flags_1_21_1 { configExactConfiguration = NoFlag
  560                                 , configStripLibs = NoFlag }
  561     -- Cabal < 1.19.1 uses '--constraint' instead of '--dependency'.
  562     flags_1_19_1 = flags_1_19_2 { configDependencies = []
  563                                 , configConstraints  = configConstraints flags }
  564     -- Cabal < 1.18.0 doesn't know about --extra-prog-path and --sysconfdir.
  565     flags_1_18_0 = flags_1_19_1 { configProgramPathExtra = toNubList []
  566                                 , configInstallDirs = configInstallDirs_1_18_0}
  567     configInstallDirs_1_18_0 = (configInstallDirs flags_1_19_1) { sysconfdir = NoFlag }
  568     -- Cabal < 1.14.0 doesn't know about '--disable-benchmarks'.
  569     flags_1_14_0 = flags_1_18_0 { configBenchmarks  = NoFlag }
  570     -- Cabal < 1.12.0 doesn't know about '--enable/disable-executable-dynamic'
  571     -- and '--enable/disable-library-coverage'.
  572     flags_1_12_0 = flags_1_14_0 { configLibCoverage = NoFlag
  573                                 , configDynExe      = NoFlag }
  574     -- Cabal < 1.10.0 doesn't know about '--disable-tests'.
  575     flags_1_10_0 = flags_1_12_0 { configTests       = NoFlag }
  576     -- Cabal < 1.3.10 does not grok the '--constraints' flag.
  577     flags_1_3_10 = flags_1_10_0 { configConstraints = [] }
  578 
  579 -- | Get the package database settings from 'ConfigFlags', accounting for
  580 -- @--package-db@ and @--user@ flags.
  581 configPackageDB' :: ConfigFlags -> PackageDBStack
  582 configPackageDB' cfg =
  583     interpretPackageDbFlags userInstall (configPackageDBs cfg)
  584   where
  585     userInstall = Cabal.fromFlagOrDefault True (configUserInstall cfg)
  586 
  587 -- | Configure the compiler, but reduce verbosity during this step.
  588 configCompilerAux' :: ConfigFlags -> IO (Compiler, Platform, ProgramDb)
  589 configCompilerAux' configFlags =
  590   configCompilerAuxEx configFlags
  591     --FIXME: make configCompilerAux use a sensible verbosity
  592     { configVerbosity = fmap lessVerbose (configVerbosity configFlags) }
  593 
  594 -- ------------------------------------------------------------
  595 -- * Config extra flags
  596 -- ------------------------------------------------------------
  597 
  598 -- | cabal configure takes some extra flags beyond runghc Setup configure
  599 --
  600 data ConfigExFlags = ConfigExFlags {
  601     configCabalVersion  :: Flag Version,
  602     configExConstraints :: [(UserConstraint, ConstraintSource)],
  603     configPreferences   :: [PackageVersionConstraint],
  604     configSolver        :: Flag PreSolver,
  605     configAllowNewer    :: Maybe AllowNewer,
  606     configAllowOlder    :: Maybe AllowOlder,
  607     configWriteGhcEnvironmentFilesPolicy
  608       :: Flag WriteGhcEnvironmentFilesPolicy
  609   }
  610   deriving (Eq, Show, Generic)
  611 
  612 defaultConfigExFlags :: ConfigExFlags
  613 defaultConfigExFlags = mempty { configSolver     = Flag defaultSolver }
  614 
  615 configureExCommand :: CommandUI (ConfigFlags, ConfigExFlags)
  616 configureExCommand = configureCommand {
  617     commandDefaultFlags = (mempty, defaultConfigExFlags),
  618     commandOptions      = \showOrParseArgs ->
  619          liftOptions fst setFst
  620          (filter ((`notElem` ["constraint", "dependency", "exact-configuration"])
  621                   . optionName) $ configureOptions  showOrParseArgs)
  622       ++ liftOptions snd setSnd
  623          (configureExOptions showOrParseArgs ConstraintSourceCommandlineFlag)
  624   }
  625   where
  626     setFst a (_,b) = (a,b)
  627     setSnd b (a,_) = (a,b)
  628 
  629 configureExOptions :: ShowOrParseArgs
  630                    -> ConstraintSource
  631                    -> [OptionField ConfigExFlags]
  632 configureExOptions _showOrParseArgs src =
  633   [ option [] ["cabal-lib-version"]
  634       ("Select which version of the Cabal lib to use to build packages "
  635       ++ "(useful for testing).")
  636       configCabalVersion (\v flags -> flags { configCabalVersion = v })
  637       (reqArg "VERSION" (parsecToReadE ("Cannot parse cabal lib version: "++)
  638                                     (fmap toFlag parsec))
  639                         (map prettyShow. flagToList))
  640   , option [] ["constraint"]
  641       "Specify constraints on a package (version, installed/source, flags)"
  642       configExConstraints (\v flags -> flags { configExConstraints = v })
  643       (reqArg "CONSTRAINT"
  644               ((\x -> [(x, src)]) `fmap` ReadE readUserConstraint)
  645               (map $ prettyShow . fst))
  646 
  647   , option [] ["preference"]
  648       "Specify preferences (soft constraints) on the version of a package"
  649       configPreferences (\v flags -> flags { configPreferences = v })
  650       (reqArg "CONSTRAINT"
  651               (parsecToReadE (const "dependency expected")
  652                           (fmap (\x -> [x]) parsec))
  653               (map prettyShow))
  654 
  655   , optionSolver configSolver (\v flags -> flags { configSolver = v })
  656 
  657   , option [] ["allow-older"]
  658     ("Ignore lower bounds in all dependencies or DEPS")
  659     (fmap unAllowOlder . configAllowOlder)
  660     (\v flags -> flags { configAllowOlder = fmap AllowOlder v})
  661     (optArg "DEPS"
  662      (parsecToReadE ("Cannot parse the list of packages: " ++) relaxDepsParser)
  663      (Just RelaxDepsAll) relaxDepsPrinter)
  664 
  665   , option [] ["allow-newer"]
  666     ("Ignore upper bounds in all dependencies or DEPS")
  667     (fmap unAllowNewer . configAllowNewer)
  668     (\v flags -> flags { configAllowNewer = fmap AllowNewer v})
  669     (optArg "DEPS"
  670      (parsecToReadE ("Cannot parse the list of packages: " ++) relaxDepsParser)
  671      (Just RelaxDepsAll) relaxDepsPrinter)
  672 
  673   , option [] ["write-ghc-environment-files"]
  674     ("Whether to create a .ghc.environment file after a successful build"
  675       ++ " (v2-build only)")
  676     configWriteGhcEnvironmentFilesPolicy
  677     (\v flags -> flags { configWriteGhcEnvironmentFilesPolicy = v})
  678     (reqArg "always|never|ghc8.4.4+"
  679      writeGhcEnvironmentFilesPolicyParser
  680      writeGhcEnvironmentFilesPolicyPrinter)
  681   ]
  682 
  683 
  684 writeGhcEnvironmentFilesPolicyParser :: ReadE (Flag WriteGhcEnvironmentFilesPolicy)
  685 writeGhcEnvironmentFilesPolicyParser = ReadE $ \case
  686   "always"    -> Right $ Flag AlwaysWriteGhcEnvironmentFiles
  687   "never"     -> Right $ Flag NeverWriteGhcEnvironmentFiles
  688   "ghc8.4.4+" -> Right $ Flag WriteGhcEnvironmentFilesOnlyForGhc844AndNewer
  689   policy      -> Left  $ "Cannot parse the GHC environment file write policy '"
  690                  <> policy <> "'"
  691 
  692 writeGhcEnvironmentFilesPolicyPrinter
  693   :: Flag WriteGhcEnvironmentFilesPolicy -> [String]
  694 writeGhcEnvironmentFilesPolicyPrinter = \case
  695   (Flag AlwaysWriteGhcEnvironmentFiles)                -> ["always"]
  696   (Flag NeverWriteGhcEnvironmentFiles)                 -> ["never"]
  697   (Flag WriteGhcEnvironmentFilesOnlyForGhc844AndNewer) -> ["ghc8.4.4+"]
  698   NoFlag                                               -> []
  699 
  700 
  701 relaxDepsParser :: CabalParsing m => m (Maybe RelaxDeps)
  702 relaxDepsParser =
  703   (Just . RelaxDepsSome . toList) `fmap` P.sepByNonEmpty parsec (P.char ',')
  704 
  705 relaxDepsPrinter :: (Maybe RelaxDeps) -> [Maybe String]
  706 relaxDepsPrinter Nothing                     = []
  707 relaxDepsPrinter (Just RelaxDepsAll)         = [Nothing]
  708 relaxDepsPrinter (Just (RelaxDepsSome pkgs)) = map (Just . prettyShow) $ pkgs
  709 
  710 
  711 instance Monoid ConfigExFlags where
  712   mempty = gmempty
  713   mappend = (<>)
  714 
  715 instance Semigroup ConfigExFlags where
  716   (<>) = gmappend
  717 
  718 reconfigureCommand :: CommandUI (ConfigFlags, ConfigExFlags)
  719 reconfigureCommand
  720   = configureExCommand
  721     { commandName         = "reconfigure"
  722     , commandSynopsis     = "Reconfigure the package if necessary."
  723     , commandDescription  = Just $ \pname -> wrapText $
  724          "Run `configure` with the most recently used flags, or append FLAGS "
  725          ++ "to the most recently used configuration. "
  726          ++ "Accepts the same flags as `" ++ pname ++ " v1-configure'. "
  727          ++ "If the package has never been configured, the default flags are "
  728          ++ "used."
  729     , commandNotes        = Just $ \pname ->
  730         "Examples:\n"
  731         ++ "  " ++ pname ++ " v1-reconfigure\n"
  732         ++ "    Configure with the most recently used flags.\n"
  733         ++ "  " ++ pname ++ " v1-reconfigure -w PATH\n"
  734         ++ "    Reconfigure with the most recently used flags,\n"
  735         ++ "    but use the compiler at PATH.\n\n"
  736     , commandUsage        = usageAlternatives "v1-reconfigure" [ "[FLAGS]" ]
  737     , commandDefaultFlags = mempty
  738     }
  739 
  740 -- ------------------------------------------------------------
  741 -- * Build flags
  742 -- ------------------------------------------------------------
  743 
  744 buildCommand :: CommandUI BuildFlags
  745 buildCommand = parent {
  746     commandName = "build",
  747     commandDescription  = Just $ \_ -> wrapText $
  748       "Components encompass executables, tests, and benchmarks.\n"
  749         ++ "\n"
  750         ++ "Affected by configuration options, see `v1-configure`.\n",
  751     commandDefaultFlags = commandDefaultFlags parent,
  752     commandUsage        = usageAlternatives "v1-build" $
  753       [ "[FLAGS]", "COMPONENTS [FLAGS]" ],
  754     commandOptions      = commandOptions parent
  755     , commandNotes      = Just $ \pname ->
  756       "Examples:\n"
  757         ++ "  " ++ pname ++ " v1-build           "
  758         ++ "    All the components in the package\n"
  759         ++ "  " ++ pname ++ " v1-build foo       "
  760         ++ "    A component (i.e. lib, exe, test suite)\n\n"
  761         ++ Cabal.programFlagsDescription defaultProgramDb
  762   }
  763   where
  764     parent = Cabal.buildCommand defaultProgramDb
  765 
  766 -- ------------------------------------------------------------
  767 -- * Test flags
  768 -- ------------------------------------------------------------
  769 
  770 -- | Given some 'TestFlags' for the version of Cabal that
  771 -- cabal-install was built with, and a target older 'Version' of
  772 -- Cabal that we want to pass these flags to, convert the
  773 -- flags into a form that will be accepted by the older
  774 -- Setup script.  Generally speaking, this just means filtering
  775 -- out flags that the old Cabal library doesn't understand, but
  776 -- in some cases it may also mean "emulating" a feature using
  777 -- some more legacy flags.
  778 filterTestFlags :: TestFlags -> Version -> TestFlags
  779 filterTestFlags flags cabalLibVersion
  780   -- NB: we expect the latest version to be the most common case,
  781   -- so test it first.
  782   | cabalLibVersion >= mkVersion [3,0,0] = flags_latest
  783   -- The naming convention is that flags_version gives flags with
  784   -- all flags *introduced* in version eliminated.
  785   -- It is NOT the latest version of Cabal library that
  786   -- these flags work for; version of introduction is a more
  787   -- natural metric.
  788   | cabalLibVersion <  mkVersion [3,0,0] = flags_3_0_0
  789   | otherwise = error "the impossible just happened" -- see first guard
  790   where
  791     flags_latest = flags
  792     flags_3_0_0  = flags_latest {
  793       -- Cabal < 3.0 doesn't know about --test-wrapper
  794       Cabal.testWrapper = NoFlag
  795       }
  796 
  797 -- ------------------------------------------------------------
  798 -- * Repl command
  799 -- ------------------------------------------------------------
  800 
  801 replCommand :: CommandUI ReplFlags
  802 replCommand = parent {
  803     commandName = "repl",
  804     commandDescription  = Just $ \pname -> wrapText $
  805          "If the current directory contains no package, ignores COMPONENT "
  806       ++ "parameters and opens an interactive interpreter session;\n"
  807       ++ "\n"
  808       ++ "Otherwise, (re)configures with the given or default flags, and "
  809       ++ "loads the interpreter with the relevant modules. For executables, "
  810       ++ "tests and benchmarks, loads the main module (and its "
  811       ++ "dependencies); for libraries all exposed/other modules.\n"
  812       ++ "\n"
  813       ++ "The default component is the library itself, or the executable "
  814       ++ "if that is the only component.\n"
  815       ++ "\n"
  816       ++ "Support for loading specific modules is planned but not "
  817       ++ "implemented yet. For certain scenarios, `" ++ pname
  818       ++ " v1-exec -- ghci :l Foo` may be used instead. Note that `v1-exec` will "
  819       ++ "not (re)configure and you will have to specify the location of "
  820       ++ "other modules, if required.\n",
  821     commandUsage =  \pname -> "Usage: " ++ pname ++ " v1-repl [COMPONENT] [FLAGS]\n",
  822     commandDefaultFlags = commandDefaultFlags parent,
  823     commandOptions      = commandOptions parent,
  824     commandNotes        = Just $ \pname ->
  825       "Examples:\n"
  826     ++ "  " ++ pname ++ " v1-repl           "
  827     ++ "    The first component in the package\n"
  828     ++ "  " ++ pname ++ " v1-repl foo       "
  829     ++ "    A named component (i.e. lib, exe, test suite)\n"
  830     ++ "  " ++ pname ++ " v1-repl --ghc-options=\"-lstdc++\""
  831     ++ "  Specifying flags for interpreter\n"
  832   }
  833   where
  834     parent = Cabal.replCommand defaultProgramDb
  835 
  836 -- ------------------------------------------------------------
  837 -- * Test command
  838 -- ------------------------------------------------------------
  839 
  840 testCommand :: CommandUI (BuildFlags, TestFlags)
  841 testCommand = parent {
  842   commandName = "test",
  843   commandDescription  = Just $ \pname -> wrapText $
  844          "If necessary (re)configures with `--enable-tests` flag and builds"
  845       ++ " the test suite.\n"
  846       ++ "\n"
  847       ++ "Remember that the tests' dependencies must be installed if there"
  848       ++ " are additional ones; e.g. with `" ++ pname
  849       ++ " v1-install --only-dependencies --enable-tests`.\n"
  850       ++ "\n"
  851       ++ "By defining UserHooks in a custom Setup.hs, the package can"
  852       ++ " define actions to be executed before and after running tests.\n",
  853   commandUsage = usageAlternatives "v1-test"
  854       [ "[FLAGS]", "TESTCOMPONENTS [FLAGS]" ],
  855   commandDefaultFlags = (Cabal.defaultBuildFlags, commandDefaultFlags parent),
  856   commandOptions      =
  857     \showOrParseArgs -> liftOptions get1 set1
  858                         (Cabal.buildOptions progDb showOrParseArgs)
  859                         ++
  860                         liftOptions get2 set2
  861                         (commandOptions parent showOrParseArgs)
  862   }
  863   where
  864     get1 (a,_) = a; set1 a (_,b) = (a,b)
  865     get2 (_,b) = b; set2 b (a,_) = (a,b)
  866 
  867     parent = Cabal.testCommand
  868     progDb = defaultProgramDb
  869 
  870 -- ------------------------------------------------------------
  871 -- * Bench command
  872 -- ------------------------------------------------------------
  873 
  874 benchmarkCommand :: CommandUI (BuildFlags, BenchmarkFlags)
  875 benchmarkCommand = parent {
  876   commandName = "bench",
  877   commandUsage = usageAlternatives "v1-bench"
  878       [ "[FLAGS]", "BENCHCOMPONENTS [FLAGS]" ],
  879   commandDescription  = Just $ \pname -> wrapText $
  880          "If necessary (re)configures with `--enable-benchmarks` flag and"
  881       ++ " builds the benchmarks.\n"
  882       ++ "\n"
  883       ++ "Remember that the benchmarks' dependencies must be installed if"
  884       ++ " there are additional ones; e.g. with `" ++ pname
  885       ++ " v1-install --only-dependencies --enable-benchmarks`.\n"
  886       ++ "\n"
  887       ++ "By defining UserHooks in a custom Setup.hs, the package can"
  888       ++ " define actions to be executed before and after running"
  889       ++ " benchmarks.\n",
  890   commandDefaultFlags = (Cabal.defaultBuildFlags, commandDefaultFlags parent),
  891   commandOptions      =
  892     \showOrParseArgs -> liftOptions get1 set1
  893                         (Cabal.buildOptions progDb showOrParseArgs)
  894                         ++
  895                         liftOptions get2 set2
  896                         (commandOptions parent showOrParseArgs)
  897   }
  898   where
  899     get1 (a,_) = a; set1 a (_,b) = (a,b)
  900     get2 (_,b) = b; set2 b (a,_) = (a,b)
  901 
  902     parent = Cabal.benchmarkCommand
  903     progDb = defaultProgramDb
  904 
  905 -- ------------------------------------------------------------
  906 -- * Fetch command
  907 -- ------------------------------------------------------------
  908 
  909 data FetchFlags = FetchFlags {
  910 --    fetchOutput    :: Flag FilePath,
  911       fetchDeps      :: Flag Bool,
  912       fetchDryRun    :: Flag Bool,
  913       fetchSolver           :: Flag PreSolver,
  914       fetchMaxBackjumps     :: Flag Int,
  915       fetchReorderGoals     :: Flag ReorderGoals,
  916       fetchCountConflicts   :: Flag CountConflicts,
  917       fetchFineGrainedConflicts :: Flag FineGrainedConflicts,
  918       fetchMinimizeConflictSet :: Flag MinimizeConflictSet,
  919       fetchIndependentGoals :: Flag IndependentGoals,
  920       fetchShadowPkgs       :: Flag ShadowPkgs,
  921       fetchStrongFlags      :: Flag StrongFlags,
  922       fetchAllowBootLibInstalls :: Flag AllowBootLibInstalls,
  923       fetchOnlyConstrained  :: Flag OnlyConstrained,
  924       fetchTests            :: Flag Bool,
  925       fetchBenchmarks       :: Flag Bool,
  926       fetchVerbosity :: Flag Verbosity
  927     }
  928 
  929 defaultFetchFlags :: FetchFlags
  930 defaultFetchFlags = FetchFlags {
  931 --  fetchOutput    = mempty,
  932     fetchDeps      = toFlag True,
  933     fetchDryRun    = toFlag False,
  934     fetchSolver           = Flag defaultSolver,
  935     fetchMaxBackjumps     = Flag defaultMaxBackjumps,
  936     fetchReorderGoals     = Flag (ReorderGoals False),
  937     fetchCountConflicts   = Flag (CountConflicts True),
  938     fetchFineGrainedConflicts = Flag (FineGrainedConflicts True),
  939     fetchMinimizeConflictSet = Flag (MinimizeConflictSet False),
  940     fetchIndependentGoals = Flag (IndependentGoals False),
  941     fetchShadowPkgs       = Flag (ShadowPkgs False),
  942     fetchStrongFlags      = Flag (StrongFlags False),
  943     fetchAllowBootLibInstalls = Flag (AllowBootLibInstalls False),
  944     fetchOnlyConstrained  = Flag OnlyConstrainedNone,
  945     fetchTests            = toFlag False,
  946     fetchBenchmarks       = toFlag False,
  947     fetchVerbosity = toFlag normal
  948    }
  949 
  950 fetchCommand :: CommandUI FetchFlags
  951 fetchCommand = CommandUI {
  952     commandName         = "fetch",
  953     commandSynopsis     = "Downloads packages for later installation.",
  954     commandUsage        = usageAlternatives "fetch" [ "[FLAGS] PACKAGES"
  955                                                     ],
  956     commandDescription  = Just $ \_ ->
  957           "Note that it currently is not possible to fetch the dependencies for a\n"
  958        ++ "package in the current directory.\n",
  959     commandNotes        = Nothing,
  960     commandDefaultFlags = defaultFetchFlags,
  961     commandOptions      = \ showOrParseArgs -> [
  962          optionVerbosity fetchVerbosity (\v flags -> flags { fetchVerbosity = v })
  963 
  964 --     , option "o" ["output"]
  965 --         "Put the package(s) somewhere specific rather than the usual cache."
  966 --         fetchOutput (\v flags -> flags { fetchOutput = v })
  967 --         (reqArgFlag "PATH")
  968 
  969        , option [] ["dependencies", "deps"]
  970            "Resolve and fetch dependencies (default)"
  971            fetchDeps (\v flags -> flags { fetchDeps = v })
  972            trueArg
  973 
  974        , option [] ["no-dependencies", "no-deps"]
  975            "Ignore dependencies"
  976            fetchDeps (\v flags -> flags { fetchDeps = v })
  977            falseArg
  978 
  979        , option [] ["dry-run"]
  980            "Do not install anything, only print what would be installed."
  981            fetchDryRun (\v flags -> flags { fetchDryRun = v })
  982            trueArg
  983 
  984       , option "" ["tests"]
  985          "dependency checking and compilation for test suites listed in the package description file."
  986          fetchTests (\v flags -> flags { fetchTests = v })
  987          (boolOpt [] [])
  988 
  989       , option "" ["benchmarks"]
  990          "dependency checking and compilation for benchmarks listed in the package description file."
  991          fetchBenchmarks (\v flags -> flags { fetchBenchmarks = v })
  992          (boolOpt [] [])
  993 
  994        ] ++
  995 
  996        optionSolver      fetchSolver           (\v flags -> flags { fetchSolver           = v }) :
  997        optionSolverFlags showOrParseArgs
  998                          fetchMaxBackjumps     (\v flags -> flags { fetchMaxBackjumps     = v })
  999                          fetchReorderGoals     (\v flags -> flags { fetchReorderGoals     = v })
 1000                          fetchCountConflicts   (\v flags -> flags { fetchCountConflicts   = v })
 1001                          fetchFineGrainedConflicts (\v flags -> flags { fetchFineGrainedConflicts = v })
 1002                          fetchMinimizeConflictSet (\v flags -> flags { fetchMinimizeConflictSet = v })
 1003                          fetchIndependentGoals (\v flags -> flags { fetchIndependentGoals = v })
 1004                          fetchShadowPkgs       (\v flags -> flags { fetchShadowPkgs       = v })
 1005                          fetchStrongFlags      (\v flags -> flags { fetchStrongFlags      = v })
 1006                          fetchAllowBootLibInstalls (\v flags -> flags { fetchAllowBootLibInstalls = v })
 1007                          fetchOnlyConstrained  (\v flags -> flags { fetchOnlyConstrained  = v })
 1008 
 1009   }
 1010 
 1011 -- ------------------------------------------------------------
 1012 -- * Freeze command
 1013 -- ------------------------------------------------------------
 1014 
 1015 data FreezeFlags = FreezeFlags {
 1016       freezeDryRun           :: Flag Bool,
 1017       freezeTests            :: Flag Bool,
 1018       freezeBenchmarks       :: Flag Bool,
 1019       freezeSolver           :: Flag PreSolver,
 1020       freezeMaxBackjumps     :: Flag Int,
 1021       freezeReorderGoals     :: Flag ReorderGoals,
 1022       freezeCountConflicts   :: Flag CountConflicts,
 1023       freezeFineGrainedConflicts :: Flag FineGrainedConflicts,
 1024       freezeMinimizeConflictSet :: Flag MinimizeConflictSet,
 1025       freezeIndependentGoals :: Flag IndependentGoals,
 1026       freezeShadowPkgs       :: Flag ShadowPkgs,
 1027       freezeStrongFlags      :: Flag StrongFlags,
 1028       freezeAllowBootLibInstalls :: Flag AllowBootLibInstalls,
 1029       freezeOnlyConstrained  :: Flag OnlyConstrained,
 1030       freezeVerbosity        :: Flag Verbosity
 1031     }
 1032 
 1033 defaultFreezeFlags :: FreezeFlags
 1034 defaultFreezeFlags = FreezeFlags {
 1035     freezeDryRun           = toFlag False,
 1036     freezeTests            = toFlag False,
 1037     freezeBenchmarks       = toFlag False,
 1038     freezeSolver           = Flag defaultSolver,
 1039     freezeMaxBackjumps     = Flag defaultMaxBackjumps,
 1040     freezeReorderGoals     = Flag (ReorderGoals False),
 1041     freezeCountConflicts   = Flag (CountConflicts True),
 1042     freezeFineGrainedConflicts = Flag (FineGrainedConflicts True),
 1043     freezeMinimizeConflictSet = Flag (MinimizeConflictSet False),
 1044     freezeIndependentGoals = Flag (IndependentGoals False),
 1045     freezeShadowPkgs       = Flag (ShadowPkgs False),
 1046     freezeStrongFlags      = Flag (StrongFlags False),
 1047     freezeAllowBootLibInstalls = Flag (AllowBootLibInstalls False),
 1048     freezeOnlyConstrained  = Flag OnlyConstrainedNone,
 1049     freezeVerbosity        = toFlag normal
 1050    }
 1051 
 1052 freezeCommand :: CommandUI FreezeFlags
 1053 freezeCommand = CommandUI {
 1054     commandName         = "freeze",
 1055     commandSynopsis     = "Freeze dependencies.",
 1056     commandDescription  = Just $ \_ -> wrapText $
 1057          "Calculates a valid set of dependencies and their exact versions. "
 1058       ++ "If successful, saves the result to the file `cabal.config`.\n"
 1059       ++ "\n"
 1060       ++ "The package versions specified in `cabal.config` will be used for "
 1061       ++ "any future installs.\n"
 1062       ++ "\n"
 1063       ++ "An existing `cabal.config` is ignored and overwritten.\n",
 1064     commandNotes        = Nothing,
 1065     commandUsage        = usageFlags "freeze",
 1066     commandDefaultFlags = defaultFreezeFlags,
 1067     commandOptions      = \ showOrParseArgs -> [
 1068          optionVerbosity freezeVerbosity
 1069          (\v flags -> flags { freezeVerbosity = v })
 1070 
 1071        , option [] ["dry-run"]
 1072            "Do not freeze anything, only print what would be frozen"
 1073            freezeDryRun (\v flags -> flags { freezeDryRun = v })
 1074            trueArg
 1075 
 1076        , option [] ["tests"]
 1077            ("freezing of the dependencies of any tests suites "
 1078             ++ "in the package description file.")
 1079            freezeTests (\v flags -> flags { freezeTests = v })
 1080            (boolOpt [] [])
 1081 
 1082        , option [] ["benchmarks"]
 1083            ("freezing of the dependencies of any benchmarks suites "
 1084             ++ "in the package description file.")
 1085            freezeBenchmarks (\v flags -> flags { freezeBenchmarks = v })
 1086            (boolOpt [] [])
 1087 
 1088        ] ++
 1089 
 1090        optionSolver
 1091          freezeSolver           (\v flags -> flags { freezeSolver           = v }):
 1092        optionSolverFlags showOrParseArgs
 1093                          freezeMaxBackjumps     (\v flags -> flags { freezeMaxBackjumps     = v })
 1094                          freezeReorderGoals     (\v flags -> flags { freezeReorderGoals     = v })
 1095                          freezeCountConflicts   (\v flags -> flags { freezeCountConflicts   = v })
 1096                          freezeFineGrainedConflicts (\v flags -> flags { freezeFineGrainedConflicts = v })
 1097                          freezeMinimizeConflictSet (\v flags -> flags { freezeMinimizeConflictSet = v })
 1098                          freezeIndependentGoals (\v flags -> flags { freezeIndependentGoals = v })
 1099                          freezeShadowPkgs       (\v flags -> flags { freezeShadowPkgs       = v })
 1100                          freezeStrongFlags      (\v flags -> flags { freezeStrongFlags      = v })
 1101                          freezeAllowBootLibInstalls (\v flags -> flags { freezeAllowBootLibInstalls = v })
 1102                          freezeOnlyConstrained  (\v flags -> flags { freezeOnlyConstrained  = v })
 1103 
 1104   }
 1105 
 1106 -- ------------------------------------------------------------
 1107 -- * 'gen-bounds' command
 1108 -- ------------------------------------------------------------
 1109 
 1110 genBoundsCommand :: CommandUI FreezeFlags
 1111 genBoundsCommand = CommandUI {
 1112     commandName         = "gen-bounds",
 1113     commandSynopsis     = "Generate dependency bounds.",
 1114     commandDescription  = Just $ \_ -> wrapText $
 1115          "Generates bounds for all dependencies that do not currently have them. "
 1116       ++ "Generated bounds are printed to stdout.  "
 1117       ++ "You can then paste them into your .cabal file.\n"
 1118       ++ "\n",
 1119     commandNotes        = Nothing,
 1120     commandUsage        = usageFlags "gen-bounds",
 1121     commandDefaultFlags = defaultFreezeFlags,
 1122     commandOptions      = \ _ -> [
 1123      optionVerbosity freezeVerbosity (\v flags -> flags { freezeVerbosity = v })
 1124      ]
 1125   }
 1126 
 1127 -- ------------------------------------------------------------
 1128 -- * 'outdated' command
 1129 -- ------------------------------------------------------------
 1130 
 1131 data IgnoreMajorVersionBumps = IgnoreMajorVersionBumpsNone
 1132                              | IgnoreMajorVersionBumpsAll
 1133                              | IgnoreMajorVersionBumpsSome [PackageName]
 1134 
 1135 instance Monoid IgnoreMajorVersionBumps where
 1136   mempty  = IgnoreMajorVersionBumpsNone
 1137   mappend = (<>)
 1138 
 1139 instance Semigroup IgnoreMajorVersionBumps where
 1140   IgnoreMajorVersionBumpsNone       <> r                               = r
 1141   l@IgnoreMajorVersionBumpsAll      <> _                               = l
 1142   l@(IgnoreMajorVersionBumpsSome _) <> IgnoreMajorVersionBumpsNone     = l
 1143   (IgnoreMajorVersionBumpsSome   _) <> r@IgnoreMajorVersionBumpsAll    = r
 1144   (IgnoreMajorVersionBumpsSome   a) <> (IgnoreMajorVersionBumpsSome b) =
 1145     IgnoreMajorVersionBumpsSome (a ++ b)
 1146 
 1147 data OutdatedFlags = OutdatedFlags {
 1148   outdatedVerbosity     :: Flag Verbosity,
 1149   outdatedFreezeFile    :: Flag Bool,
 1150   outdatedNewFreezeFile :: Flag Bool,
 1151   outdatedProjectFile   :: Flag FilePath,
 1152   outdatedSimpleOutput  :: Flag Bool,
 1153   outdatedExitCode      :: Flag Bool,
 1154   outdatedQuiet         :: Flag Bool,
 1155   outdatedIgnore        :: [PackageName],
 1156   outdatedMinor         :: Maybe IgnoreMajorVersionBumps
 1157   }
 1158 
 1159 defaultOutdatedFlags :: OutdatedFlags
 1160 defaultOutdatedFlags = OutdatedFlags {
 1161   outdatedVerbosity     = toFlag normal,
 1162   outdatedFreezeFile    = mempty,
 1163   outdatedNewFreezeFile = mempty,
 1164   outdatedProjectFile   = mempty,
 1165   outdatedSimpleOutput  = mempty,
 1166   outdatedExitCode      = mempty,
 1167   outdatedQuiet         = mempty,
 1168   outdatedIgnore        = mempty,
 1169   outdatedMinor         = mempty
 1170   }
 1171 
 1172 outdatedCommand :: CommandUI OutdatedFlags
 1173 outdatedCommand = CommandUI {
 1174   commandName = "outdated",
 1175   commandSynopsis = "Check for outdated dependencies",
 1176   commandDescription  = Just $ \_ -> wrapText $
 1177     "Checks for outdated dependencies in the package description file "
 1178     ++ "or freeze file",
 1179   commandNotes = Nothing,
 1180   commandUsage = usageFlags "outdated",
 1181   commandDefaultFlags = defaultOutdatedFlags,
 1182   commandOptions      = \ _ -> [
 1183     optionVerbosity outdatedVerbosity
 1184       (\v flags -> flags { outdatedVerbosity = v })
 1185 
 1186     ,option [] ["freeze-file", "v1-freeze-file"]
 1187      "Act on the freeze file"
 1188      outdatedFreezeFile (\v flags -> flags { outdatedFreezeFile = v })
 1189      trueArg
 1190 
 1191     ,option [] ["v2-freeze-file", "new-freeze-file"]
 1192      "Act on the new-style freeze file (default: cabal.project.freeze)"
 1193      outdatedNewFreezeFile (\v flags -> flags { outdatedNewFreezeFile = v })
 1194      trueArg
 1195 
 1196     ,option [] ["project-file"]
 1197      "Act on the new-style freeze file named PROJECTFILE.freeze rather than the default cabal.project.freeze"
 1198      outdatedProjectFile (\v flags -> flags { outdatedProjectFile = v })
 1199      (reqArgFlag "PROJECTFILE")
 1200 
 1201     ,option [] ["simple-output"]
 1202      "Only print names of outdated dependencies, one per line"
 1203      outdatedSimpleOutput (\v flags -> flags { outdatedSimpleOutput = v })
 1204      trueArg
 1205 
 1206     ,option [] ["exit-code"]
 1207      "Exit with non-zero when there are outdated dependencies"
 1208      outdatedExitCode (\v flags -> flags { outdatedExitCode = v })
 1209      trueArg
 1210 
 1211     ,option ['q'] ["quiet"]
 1212      "Don't print any output. Implies '--exit-code' and '-v0'"
 1213      outdatedQuiet (\v flags -> flags { outdatedQuiet = v })
 1214      trueArg
 1215 
 1216    ,option [] ["ignore"]
 1217     "Packages to ignore"
 1218     outdatedIgnore (\v flags -> flags { outdatedIgnore = v })
 1219     (reqArg "PKGS" pkgNameListParser (map prettyShow))
 1220 
 1221    ,option [] ["minor"]
 1222     "Ignore major version bumps for these packages"
 1223     outdatedMinor (\v flags -> flags { outdatedMinor = v })
 1224     (optArg "PKGS" ignoreMajorVersionBumpsParser
 1225       (Just IgnoreMajorVersionBumpsAll) ignoreMajorVersionBumpsPrinter)
 1226    ]
 1227   }
 1228   where
 1229     ignoreMajorVersionBumpsPrinter :: (Maybe IgnoreMajorVersionBumps)
 1230                                    -> [Maybe String]
 1231     ignoreMajorVersionBumpsPrinter Nothing = []
 1232     ignoreMajorVersionBumpsPrinter (Just IgnoreMajorVersionBumpsNone)= []
 1233     ignoreMajorVersionBumpsPrinter (Just IgnoreMajorVersionBumpsAll) = [Nothing]
 1234     ignoreMajorVersionBumpsPrinter (Just (IgnoreMajorVersionBumpsSome pkgs)) =
 1235       map (Just . prettyShow) $ pkgs
 1236 
 1237     ignoreMajorVersionBumpsParser  =
 1238       (Just . IgnoreMajorVersionBumpsSome) `fmap` pkgNameListParser
 1239 
 1240     pkgNameListParser = parsecToReadE
 1241       ("Couldn't parse the list of package names: " ++)
 1242       (fmap toList (P.sepByNonEmpty parsec (P.char ',')))
 1243 
 1244 -- ------------------------------------------------------------
 1245 -- * Update command
 1246 -- ------------------------------------------------------------
 1247 
 1248 data UpdateFlags
 1249     = UpdateFlags {
 1250         updateVerbosity  :: Flag Verbosity,
 1251         updateIndexState :: Flag TotalIndexState
 1252     } deriving Generic
 1253 
 1254 defaultUpdateFlags :: UpdateFlags
 1255 defaultUpdateFlags
 1256     = UpdateFlags {
 1257         updateVerbosity  = toFlag normal,
 1258         updateIndexState = toFlag headTotalIndexState
 1259     }
 1260 
 1261 -- ------------------------------------------------------------
 1262 -- * Other commands
 1263 -- ------------------------------------------------------------
 1264 
 1265 cleanCommand :: CommandUI CleanFlags
 1266 cleanCommand = Cabal.cleanCommand
 1267   { commandUsage = \pname ->
 1268     "Usage: " ++ pname ++ " v1-clean [FLAGS]\n"
 1269   }
 1270 
 1271 checkCommand  :: CommandUI (Flag Verbosity)
 1272 checkCommand = CommandUI {
 1273     commandName         = "check",
 1274     commandSynopsis     = "Check the package for common mistakes.",
 1275     commandDescription  = Just $ \_ -> wrapText $
 1276          "Expects a .cabal package file in the current directory.\n"
 1277       ++ "\n"
 1278       ++ "The checks correspond to the requirements to packages on Hackage. "
 1279       ++ "If no errors and warnings are reported, Hackage will accept this "
 1280       ++ "package.\n",
 1281     commandNotes        = Nothing,
 1282     commandUsage        = usageFlags "check",
 1283     commandDefaultFlags = toFlag normal,
 1284     commandOptions      = \_ -> [optionVerbosity id const]
 1285   }
 1286 
 1287 formatCommand  :: CommandUI (Flag Verbosity)
 1288 formatCommand = CommandUI {
 1289     commandName         = "format",
 1290     commandSynopsis     = "Reformat the .cabal file using the standard style.",
 1291     commandDescription  = Nothing,
 1292     commandNotes        = Nothing,
 1293     commandUsage        = usageAlternatives "format" ["[FILE]"],
 1294     commandDefaultFlags = toFlag normal,
 1295     commandOptions      = \_ -> []
 1296   }
 1297 
 1298 manpageCommand :: CommandUI ManpageFlags
 1299 manpageCommand = CommandUI {
 1300     commandName         = "man",
 1301     commandSynopsis     = "Outputs manpage source.",
 1302     commandDescription  = Just $ \_ ->
 1303       "Output manpage source to STDOUT.\n",
 1304     commandNotes        = Nothing,
 1305     commandUsage        = usageFlags "man",
 1306     commandDefaultFlags = defaultManpageFlags,
 1307     commandOptions      = manpageOptions
 1308   }
 1309 
 1310 runCommand :: CommandUI BuildFlags
 1311 runCommand = CommandUI {
 1312     commandName         = "run",
 1313     commandSynopsis     = "Builds and runs an executable.",
 1314     commandDescription  = Just $ \pname -> wrapText $
 1315          "Builds and then runs the specified executable. If no executable is "
 1316       ++ "specified, but the package contains just one executable, that one "
 1317       ++ "is built and executed.\n"
 1318       ++ "\n"
 1319       ++ "Use `" ++ pname ++ " v1-test --show-details=streaming` to run a "
 1320       ++ "test-suite and get its full output.\n",
 1321     commandNotes        = Just $ \pname ->
 1322           "Examples:\n"
 1323        ++ "  " ++ pname ++ " v1-run\n"
 1324        ++ "    Run the only executable in the current package;\n"
 1325        ++ "  " ++ pname ++ " v1-run foo -- --fooflag\n"
 1326        ++ "    Works similar to `./foo --fooflag`.\n",
 1327     commandUsage        = usageAlternatives "v1-run"
 1328         ["[FLAGS] [EXECUTABLE] [-- EXECUTABLE_FLAGS]"],
 1329     commandDefaultFlags = mempty,
 1330     commandOptions      = commandOptions parent
 1331   }
 1332   where
 1333     parent = Cabal.buildCommand defaultProgramDb
 1334 
 1335 -- ------------------------------------------------------------
 1336 -- * Report flags
 1337 -- ------------------------------------------------------------
 1338 
 1339 data ReportFlags = ReportFlags {
 1340     reportUsername  :: Flag Username,
 1341     reportPassword  :: Flag Password,
 1342     reportVerbosity :: Flag Verbosity
 1343   } deriving Generic
 1344 
 1345 defaultReportFlags :: ReportFlags
 1346 defaultReportFlags = ReportFlags {
 1347     reportUsername  = mempty,
 1348     reportPassword  = mempty,
 1349     reportVerbosity = toFlag normal
 1350   }
 1351 
 1352 reportCommand :: CommandUI ReportFlags
 1353 reportCommand = CommandUI {
 1354     commandName         = "report",
 1355     commandSynopsis     = "Upload build reports to a remote server.",
 1356     commandDescription  = Nothing,
 1357     commandNotes        = Just $ \_ ->
 1358          "You can store your Hackage login in the ~/.cabal/config file\n",
 1359     commandUsage        = usageAlternatives "report" ["[FLAGS]"],
 1360     commandDefaultFlags = defaultReportFlags,
 1361     commandOptions      = \_ ->
 1362       [optionVerbosity reportVerbosity (\v flags -> flags { reportVerbosity = v })
 1363 
 1364       ,option ['u'] ["username"]
 1365         "Hackage username."
 1366         reportUsername (\v flags -> flags { reportUsername = v })
 1367         (reqArg' "USERNAME" (toFlag . Username)
 1368                             (flagToList . fmap unUsername))
 1369 
 1370       ,option ['p'] ["password"]
 1371         "Hackage password."
 1372         reportPassword (\v flags -> flags { reportPassword = v })
 1373         (reqArg' "PASSWORD" (toFlag . Password)
 1374                             (flagToList . fmap unPassword))
 1375       ]
 1376   }
 1377 
 1378 instance Monoid ReportFlags where
 1379   mempty = gmempty
 1380   mappend = (<>)
 1381 
 1382 instance Semigroup ReportFlags where
 1383   (<>) = gmappend
 1384 
 1385 -- ------------------------------------------------------------
 1386 -- * Get flags
 1387 -- ------------------------------------------------------------
 1388 
 1389 data GetFlags = GetFlags {
 1390     getDestDir          :: Flag FilePath,
 1391     getPristine         :: Flag Bool,
 1392     getIndexState       :: Flag TotalIndexState,
 1393     getActiveRepos      :: Flag ActiveRepos,
 1394     getSourceRepository :: Flag (Maybe RepoKind),
 1395     getVerbosity        :: Flag Verbosity
 1396   } deriving Generic
 1397 
 1398 defaultGetFlags :: GetFlags
 1399 defaultGetFlags = GetFlags {
 1400     getDestDir          = mempty,
 1401     getPristine         = mempty,
 1402     getIndexState       = mempty,
 1403     getActiveRepos      = mempty,
 1404     getSourceRepository = mempty,
 1405     getVerbosity        = toFlag normal
 1406    }
 1407 
 1408 getCommand :: CommandUI GetFlags
 1409 getCommand = CommandUI {
 1410     commandName         = "get",
 1411     commandSynopsis     = "Download/Extract a package's source code (repository).",
 1412     commandDescription  = Just $ \_ -> wrapText $
 1413           "Creates a local copy of a package's source code. By default it gets "
 1414        ++ "the source\ntarball and unpacks it in a local subdirectory. "
 1415        ++ "Alternatively, with -s it will\nget the code from the source "
 1416        ++ "repository specified by the package.\n",
 1417     commandNotes        = Just $ \pname ->
 1418           "Examples:\n"
 1419        ++ "  " ++ pname ++ " get hlint\n"
 1420        ++ "    Download the latest stable version of hlint;\n"
 1421        ++ "  " ++ pname ++ " get lens --source-repository=head\n"
 1422        ++ "    Download the source repository (i.e. git clone from github).\n",
 1423     commandUsage        = usagePackages "get",
 1424     commandDefaultFlags = defaultGetFlags,
 1425     commandOptions      = \_ -> [
 1426         optionVerbosity getVerbosity (\v flags -> flags { getVerbosity = v })
 1427 
 1428        ,option "d" ["destdir"]
 1429          "Where to place the package source, defaults to the current directory."
 1430          getDestDir (\v flags -> flags { getDestDir = v })
 1431          (reqArgFlag "PATH")
 1432 
 1433        ,option "s" ["source-repository"]
 1434          "Copy the package's source repository (ie git clone, darcs get, etc as appropriate)."
 1435          getSourceRepository (\v flags -> flags { getSourceRepository = v })
 1436         (optArg "[head|this|...]" (parsecToReadE (const "invalid source-repository")
 1437                                               (fmap (toFlag . Just) parsec))
 1438                                   (Flag Nothing)
 1439                                   (map (fmap show) . flagToList))
 1440 
 1441       , option [] ["index-state"]
 1442           ("Use source package index state as it existed at a previous time. " ++
 1443            "Accepts unix-timestamps (e.g. '@1474732068'), ISO8601 UTC timestamps " ++
 1444            "(e.g. '2016-09-24T17:47:48Z'), or 'HEAD' (default: 'HEAD'). " ++
 1445            "This determines which package versions are available as well as " ++
 1446            ".cabal file revision is selected (unless --pristine is used).")
 1447           getIndexState (\v flags -> flags { getIndexState = v })
 1448           (reqArg "STATE" (parsecToReadE (const $ "index-state must be a  " ++
 1449                                        "unix-timestamps (e.g. '@1474732068'), " ++
 1450                                        "a ISO8601 UTC timestamp " ++
 1451                                        "(e.g. '2016-09-24T17:47:48Z'), or 'HEAD'")
 1452                                       (toFlag `fmap` parsec))
 1453                           (flagToList . fmap prettyShow))
 1454 
 1455        , option [] ["pristine"]
 1456            ("Unpack the original pristine tarball, rather than updating the "
 1457            ++ ".cabal file with the latest revision from the package archive.")
 1458            getPristine (\v flags -> flags { getPristine = v })
 1459            trueArg
 1460        ]
 1461   }
 1462 
 1463 -- 'cabal unpack' is a deprecated alias for 'cabal get'.
 1464 unpackCommand :: CommandUI GetFlags
 1465 unpackCommand = getCommand {
 1466   commandName  = "unpack",
 1467   commandUsage = usagePackages "unpack"
 1468   }
 1469 
 1470 instance Monoid GetFlags where
 1471   mempty = gmempty
 1472   mappend = (<>)
 1473 
 1474 instance Semigroup GetFlags where
 1475   (<>) = gmappend
 1476 
 1477 -- ------------------------------------------------------------
 1478 -- * List flags
 1479 -- ------------------------------------------------------------
 1480 
 1481 data ListFlags = ListFlags
 1482     { listInstalled       :: Flag Bool
 1483     , listSimpleOutput    :: Flag Bool
 1484     , listCaseInsensitive :: Flag Bool
 1485     , listVerbosity       :: Flag Verbosity
 1486     , listPackageDBs      :: [Maybe PackageDB]
 1487     , listHcPath          :: Flag FilePath
 1488     }
 1489   deriving Generic
 1490 
 1491 defaultListFlags :: ListFlags
 1492 defaultListFlags = ListFlags
 1493     { listInstalled       = Flag False
 1494     , listSimpleOutput    = Flag False
 1495     , listCaseInsensitive = Flag True
 1496     , listVerbosity       = toFlag normal
 1497     , listPackageDBs      = []
 1498     , listHcPath          = mempty
 1499     }
 1500 
 1501 listCommand  :: CommandUI ListFlags
 1502 listCommand = CommandUI {
 1503     commandName         = "list",
 1504     commandSynopsis     = "List packages matching a search string.",
 1505     commandDescription  = Just $ \_ -> wrapText $
 1506          "List all packages, or all packages matching one of the search"
 1507       ++ " strings.\n"
 1508       ++ "\n"
 1509       ++ "Use the package database specified with --package-db. "
 1510       ++ "If not specified, use the user package database.\n",
 1511     commandNotes        = Just $ \pname ->
 1512          "Examples:\n"
 1513       ++ "  " ++ pname ++ " list pandoc\n"
 1514       ++ "    Will find pandoc, pandoc-citeproc, pandoc-lens, ...\n",
 1515     commandUsage        = usageAlternatives "list" [ "[FLAGS]"
 1516                                                    , "[FLAGS] STRINGS"],
 1517     commandDefaultFlags = defaultListFlags,
 1518     commandOptions      = const listOptions
 1519   }
 1520 
 1521 listOptions :: [OptionField ListFlags]
 1522 listOptions =
 1523     [ optionVerbosity listVerbosity (\v flags -> flags { listVerbosity = v })
 1524 
 1525     , option [] ["installed"]
 1526         "Only print installed packages"
 1527         listInstalled (\v flags -> flags { listInstalled = v })
 1528         trueArg
 1529 
 1530     , option [] ["simple-output"]
 1531         "Print in a easy-to-parse format"
 1532         listSimpleOutput (\v flags -> flags { listSimpleOutput = v })
 1533         trueArg
 1534     , option ['i'] ["ignore-case"]
 1535         "Ignore case destictions"
 1536         listCaseInsensitive (\v flags -> flags { listCaseInsensitive = v })
 1537         (boolOpt' (['i'], ["ignore-case"]) (['I'], ["strict-case"]))
 1538 
 1539     , option "" ["package-db"]
 1540       (   "Append the given package database to the list of package"
 1541        ++ " databases used (to satisfy dependencies and register into)."
 1542        ++ " May be a specific file, 'global' or 'user'. The initial list"
 1543        ++ " is ['global'], ['global', 'user'],"
 1544        ++ " depending on context. Use 'clear' to reset the list to empty."
 1545        ++ " See the user guide for details.")
 1546       listPackageDBs (\v flags -> flags { listPackageDBs = v })
 1547       (reqArg' "DB" readPackageDbList showPackageDbList)
 1548 
 1549     , option "w" ["with-compiler"]
 1550       "give the path to a particular compiler"
 1551       listHcPath (\v flags -> flags { listHcPath = v })
 1552       (reqArgFlag "PATH")
 1553     ]
 1554 
 1555 listNeedsCompiler :: ListFlags -> Bool
 1556 listNeedsCompiler f =
 1557     flagElim False (const True) (listHcPath f)
 1558     || fromFlagOrDefault False (listInstalled f)
 1559 
 1560 instance Monoid ListFlags where
 1561   mempty = gmempty
 1562   mappend = (<>)
 1563 
 1564 instance Semigroup ListFlags where
 1565   (<>) = gmappend
 1566 
 1567 -- ------------------------------------------------------------
 1568 -- * Info flags
 1569 -- ------------------------------------------------------------
 1570 
 1571 data InfoFlags = InfoFlags {
 1572     infoVerbosity  :: Flag Verbosity,
 1573     infoPackageDBs :: [Maybe PackageDB]
 1574   } deriving Generic
 1575 
 1576 defaultInfoFlags :: InfoFlags
 1577 defaultInfoFlags = InfoFlags {
 1578     infoVerbosity  = toFlag normal,
 1579     infoPackageDBs = []
 1580   }
 1581 
 1582 infoCommand  :: CommandUI InfoFlags
 1583 infoCommand = CommandUI {
 1584     commandName         = "info",
 1585     commandSynopsis     = "Display detailed information about a particular package.",
 1586     commandDescription  = Just $ \_ -> wrapText $
 1587       "Use the package database specified with --package-db. "
 1588       ++ "If not specified, use the user package database.\n",
 1589     commandNotes        = Nothing,
 1590     commandUsage        = usageAlternatives "info" ["[FLAGS] PACKAGES"],
 1591     commandDefaultFlags = defaultInfoFlags,
 1592     commandOptions      = \_ -> [
 1593         optionVerbosity infoVerbosity (\v flags -> flags { infoVerbosity = v })
 1594 
 1595         , option "" ["package-db"]
 1596           (   "Append the given package database to the list of package"
 1597            ++ " databases used (to satisfy dependencies and register into)."
 1598            ++ " May be a specific file, 'global' or 'user'. The initial list"
 1599            ++ " is ['global'], ['global', 'user'],"
 1600            ++ " depending on context. Use 'clear' to reset the list to empty."
 1601            ++ " See the user guide for details.")
 1602           infoPackageDBs (\v flags -> flags { infoPackageDBs = v })
 1603           (reqArg' "DB" readPackageDbList showPackageDbList)
 1604 
 1605         ]
 1606   }
 1607 
 1608 instance Monoid InfoFlags where
 1609   mempty = gmempty
 1610   mappend = (<>)
 1611 
 1612 instance Semigroup InfoFlags where
 1613   (<>) = gmappend
 1614 
 1615 -- ------------------------------------------------------------
 1616 -- * Install flags
 1617 -- ------------------------------------------------------------
 1618 
 1619 -- | Install takes the same flags as configure along with a few extras.
 1620 --
 1621 data InstallFlags = InstallFlags {
 1622     installDocumentation    :: Flag Bool,
 1623     installHaddockIndex     :: Flag PathTemplate,
 1624     installDest             :: Flag Cabal.CopyDest,
 1625     installDryRun           :: Flag Bool,
 1626     installOnlyDownload     :: Flag Bool,
 1627     installMaxBackjumps     :: Flag Int,
 1628     installReorderGoals     :: Flag ReorderGoals,
 1629     installCountConflicts   :: Flag CountConflicts,
 1630     installFineGrainedConflicts :: Flag FineGrainedConflicts,
 1631     installMinimizeConflictSet :: Flag MinimizeConflictSet,
 1632     installIndependentGoals :: Flag IndependentGoals,
 1633     installShadowPkgs       :: Flag ShadowPkgs,
 1634     installStrongFlags      :: Flag StrongFlags,
 1635     installAllowBootLibInstalls :: Flag AllowBootLibInstalls,
 1636     installOnlyConstrained  :: Flag OnlyConstrained,
 1637     installReinstall        :: Flag Bool,
 1638     installAvoidReinstalls  :: Flag AvoidReinstalls,
 1639     installOverrideReinstall :: Flag Bool,
 1640     installUpgradeDeps      :: Flag Bool,
 1641     installOnly             :: Flag Bool,
 1642     installOnlyDeps         :: Flag Bool,
 1643     installIndexState       :: Flag TotalIndexState,
 1644     installRootCmd          :: Flag String,
 1645     installSummaryFile      :: NubList PathTemplate,
 1646     installLogFile          :: Flag PathTemplate,
 1647     installBuildReports     :: Flag ReportLevel,
 1648     installReportPlanningFailure :: Flag Bool,
 1649     -- Note: symlink-bindir is no longer used by v2-install and can be removed
 1650     -- when removing v1 commands
 1651     installSymlinkBinDir    :: Flag FilePath,
 1652     installPerComponent     :: Flag Bool,
 1653     installOneShot          :: Flag Bool,
 1654     installNumJobs          :: Flag (Maybe Int),
 1655     installKeepGoing        :: Flag Bool,
 1656     installRunTests         :: Flag Bool,
 1657     installOfflineMode      :: Flag Bool
 1658   }
 1659   deriving (Eq, Show, Generic)
 1660 
 1661 instance Binary InstallFlags
 1662 
 1663 defaultInstallFlags :: InstallFlags
 1664 defaultInstallFlags = InstallFlags {
 1665     installDocumentation   = Flag False,
 1666     installHaddockIndex    = Flag docIndexFile,
 1667     installDest            = Flag Cabal.NoCopyDest,
 1668     installDryRun          = Flag False,
 1669     installOnlyDownload    = Flag False,
 1670     installMaxBackjumps    = Flag defaultMaxBackjumps,
 1671     installReorderGoals    = Flag (ReorderGoals False),
 1672     installCountConflicts  = Flag (CountConflicts True),
 1673     installFineGrainedConflicts = Flag (FineGrainedConflicts True),
 1674     installMinimizeConflictSet = Flag (MinimizeConflictSet False),
 1675     installIndependentGoals= Flag (IndependentGoals False),
 1676     installShadowPkgs      = Flag (ShadowPkgs False),
 1677     installStrongFlags     = Flag (StrongFlags False),
 1678     installAllowBootLibInstalls = Flag (AllowBootLibInstalls False),
 1679     installOnlyConstrained = Flag OnlyConstrainedNone,
 1680     installReinstall       = Flag False,
 1681     installAvoidReinstalls = Flag (AvoidReinstalls False),
 1682     installOverrideReinstall = Flag False,
 1683     installUpgradeDeps     = Flag False,
 1684     installOnly            = Flag False,
 1685     installOnlyDeps        = Flag False,
 1686     installIndexState      = mempty,
 1687     installRootCmd         = mempty,
 1688     installSummaryFile     = mempty,
 1689     installLogFile         = mempty,
 1690     installBuildReports    = Flag NoReports,
 1691     installReportPlanningFailure = Flag False,
 1692     installSymlinkBinDir   = mempty,
 1693     installPerComponent    = Flag True,
 1694     installOneShot         = Flag False,
 1695     installNumJobs         = mempty,
 1696     installKeepGoing       = Flag False,
 1697     installRunTests        = mempty,
 1698     installOfflineMode     = Flag False
 1699   }
 1700   where
 1701     docIndexFile = toPathTemplate ("$datadir" </> "doc"
 1702                                    </> "$arch-$os-$compiler" </> "index.html")
 1703 
 1704 defaultMaxBackjumps :: Int
 1705 defaultMaxBackjumps = 4000
 1706 
 1707 defaultSolver :: PreSolver
 1708 defaultSolver = AlwaysModular
 1709 
 1710 allSolvers :: String
 1711 allSolvers = intercalate ", " (map prettyShow ([minBound .. maxBound] :: [PreSolver]))
 1712 
 1713 installCommand :: CommandUI ( ConfigFlags, ConfigExFlags, InstallFlags
 1714                             , HaddockFlags, TestFlags, BenchmarkFlags
 1715                             )
 1716 installCommand = CommandUI {
 1717   commandName         = "install",
 1718   commandSynopsis     = "Install packages.",
 1719   commandUsage        = usageAlternatives "v1-install" [ "[FLAGS]"
 1720                                                     , "[FLAGS] PACKAGES"
 1721                                                     ],
 1722   commandDescription  = Just $ \_ -> wrapText $
 1723         "Installs one or more packages. By default, the installed package"
 1724      ++ " will be registered in the user's package database."
 1725      ++ "\n"
 1726      ++ "If PACKAGES are specified, downloads and installs those packages."
 1727      ++ " Otherwise, install the package in the current directory (and/or its"
 1728      ++ " dependencies) (there must be exactly one .cabal file in the current"
 1729      ++ " directory).\n"
 1730      ++ "\n"
 1731      ++ "The flags to `v1-install` are saved and"
 1732      ++ " affect future commands such as `v1-build` and `v1-repl`. See the help for"
 1733      ++ " `v1-configure` for a list of commands being affected.\n"
 1734      ++ "\n"
 1735      ++ "Installed executables will by default"
 1736      ++ " be put into `~/.cabal/bin/`."
 1737      ++ " If you want installed executable to be available globally, make"
 1738      ++ " sure that the PATH environment variable contains that directory.\n"
 1739      ++ "\n",
 1740   commandNotes        = Just $ \pname ->
 1741         ( case commandNotes
 1742                $ Cabal.configureCommand defaultProgramDb
 1743           of Just desc -> desc pname ++ "\n"
 1744              Nothing   -> ""
 1745         )
 1746      ++ "Examples:\n"
 1747      ++ "  " ++ pname ++ " v1-install                 "
 1748      ++ "    Package in the current directory\n"
 1749      ++ "  " ++ pname ++ " v1-install foo             "
 1750      ++ "    Package from the hackage server\n"
 1751      ++ "  " ++ pname ++ " v1-install foo-1.0         "
 1752      ++ "    Specific version of a package\n"
 1753      ++ "  " ++ pname ++ " v1-install 'foo < 2'       "
 1754      ++ "    Constrained package version\n"
 1755      ++ "  " ++ pname ++ " v1-install haddock --bindir=$HOME/hask-bin/ --datadir=$HOME/hask-data/\n"
 1756      ++ "  " ++ (map (const ' ') pname)
 1757                       ++ "                         "
 1758      ++ "    Change installation destination\n",
 1759   commandDefaultFlags = (mempty, mempty, mempty, mempty, mempty, mempty),
 1760   commandOptions      = \showOrParseArgs ->
 1761        liftOptions get1 set1
 1762        -- Note: [Hidden Flags]
 1763        -- hide "constraint", "dependency", and
 1764        -- "exact-configuration" from the configure options.
 1765        (filter ((`notElem` ["constraint", "dependency"
 1766                            , "exact-configuration"])
 1767                 . optionName) $
 1768                               configureOptions   showOrParseArgs)
 1769     ++ liftOptions get2 set2 (configureExOptions showOrParseArgs ConstraintSourceCommandlineFlag)
 1770     ++ liftOptions get3 set3
 1771        -- hide "target-package-db" flag from the
 1772        -- install options.
 1773        (filter ((`notElem` ["target-package-db"])
 1774                 . optionName) $
 1775                               installOptions     showOrParseArgs)
 1776     ++ liftOptions get4 set4 (haddockOptions     showOrParseArgs)
 1777     ++ liftOptions get5 set5 (testOptions        showOrParseArgs)
 1778     ++ liftOptions get6 set6 (benchmarkOptions   showOrParseArgs)
 1779   }
 1780   where
 1781     get1 (a,_,_,_,_,_) = a; set1 a (_,b,c,d,e,f) = (a,b,c,d,e,f)
 1782     get2 (_,b,_,_,_,_) = b; set2 b (a,_,c,d,e,f) = (a,b,c,d,e,f)
 1783     get3 (_,_,c,_,_,_) = c; set3 c (a,b,_,d,e,f) = (a,b,c,d,e,f)
 1784     get4 (_,_,_,d,_,_) = d; set4 d (a,b,c,_,e,f) = (a,b,c,d,e,f)
 1785     get5 (_,_,_,_,e,_) = e; set5 e (a,b,c,d,_,f) = (a,b,c,d,e,f)
 1786     get6 (_,_,_,_,_,f) = f; set6 f (a,b,c,d,e,_) = (a,b,c,d,e,f)
 1787 
 1788 haddockCommand :: CommandUI HaddockFlags
 1789 haddockCommand = Cabal.haddockCommand
 1790   { commandUsage = usageAlternatives "v1-haddock" $
 1791       [ "[FLAGS]", "COMPONENTS [FLAGS]" ]
 1792   }
 1793 
 1794 filterHaddockArgs :: [String] -> Version -> [String]
 1795 filterHaddockArgs args cabalLibVersion
 1796   | cabalLibVersion >= mkVersion [2,3,0] = args_latest
 1797   | cabalLibVersion < mkVersion [2,3,0] = args_2_3_0
 1798   | otherwise = args_latest
 1799   where
 1800     args_latest = args
 1801 
 1802     -- Cabal < 2.3 doesn't know about per-component haddock
 1803     args_2_3_0 = []
 1804 
 1805 filterHaddockFlags :: HaddockFlags -> Version -> HaddockFlags
 1806 filterHaddockFlags flags cabalLibVersion
 1807   | cabalLibVersion >= mkVersion [2,3,0] = flags_latest
 1808   | cabalLibVersion < mkVersion [2,3,0] = flags_2_3_0
 1809   | otherwise = flags_latest
 1810   where
 1811     flags_latest = flags
 1812 
 1813     flags_2_3_0 = flags_latest {
 1814       -- Cabal < 2.3 doesn't know about per-component haddock
 1815       haddockArgs = []
 1816       }
 1817 
 1818 haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
 1819 haddockOptions showOrParseArgs
 1820   = [ opt { optionName = "haddock-" ++ name,
 1821             optionDescr = [ fmapOptFlags (\(_, lflags) -> ([], map ("haddock-" ++) lflags)) descr
 1822                           | descr <- optionDescr opt] }
 1823     | opt <- commandOptions Cabal.haddockCommand showOrParseArgs
 1824     , let name = optionName opt
 1825     , name `elem` ["hoogle", "html", "html-location"
 1826                   ,"executables", "tests", "benchmarks", "all", "internal", "css"
 1827                   ,"hyperlink-source", "quickjump", "hscolour-css"
 1828                   ,"contents-location", "for-hackage"]
 1829     ]
 1830 
 1831 testOptions :: ShowOrParseArgs -> [OptionField TestFlags]
 1832 testOptions showOrParseArgs
 1833   = [ opt { optionName = prefixTest name,
 1834             optionDescr = [ fmapOptFlags (\(_, lflags) -> ([], map prefixTest lflags)) descr
 1835                           | descr <- optionDescr opt] }
 1836     | opt <- commandOptions Cabal.testCommand showOrParseArgs
 1837     , let name = optionName opt
 1838     , name `elem` ["log", "machine-log", "show-details", "keep-tix-files"
 1839                   ,"fail-when-no-test-suites", "test-options", "test-option"
 1840                   ,"test-wrapper"]
 1841     ]
 1842   where
 1843     prefixTest name | "test-" `isPrefixOf` name = name
 1844                     | otherwise = "test-" ++ name
 1845 
 1846 benchmarkOptions :: ShowOrParseArgs -> [OptionField BenchmarkFlags]
 1847 benchmarkOptions showOrParseArgs
 1848   = [ opt { optionName = prefixBenchmark name,
 1849             optionDescr = [ fmapOptFlags (\(_, lflags) -> ([], map prefixBenchmark lflags)) descr
 1850                           | descr <- optionDescr opt] }
 1851     | opt <- commandOptions Cabal.benchmarkCommand showOrParseArgs
 1852     , let name = optionName opt
 1853     , name `elem` ["benchmark-options", "benchmark-option"]
 1854     ]
 1855   where
 1856     prefixBenchmark name | "benchmark-" `isPrefixOf` name = name
 1857                          | otherwise = "benchmark-" ++ name
 1858 
 1859 fmapOptFlags :: (OptFlags -> OptFlags) -> OptDescr a -> OptDescr a
 1860 fmapOptFlags modify (ReqArg d f p r w)    = ReqArg d (modify f) p r w
 1861 fmapOptFlags modify (OptArg d f p r i w)  = OptArg d (modify f) p r i w
 1862 fmapOptFlags modify (ChoiceOpt xs)        = ChoiceOpt [(d, modify f, i, w) | (d, f, i, w) <- xs]
 1863 fmapOptFlags modify (BoolOpt d f1 f2 r w) = BoolOpt d (modify f1) (modify f2) r w
 1864 
 1865 installOptions ::  ShowOrParseArgs -> [OptionField InstallFlags]
 1866 installOptions showOrParseArgs =
 1867       [ option "" ["documentation"]
 1868           "building of documentation"
 1869           installDocumentation (\v flags -> flags { installDocumentation = v })
 1870           (boolOpt [] [])
 1871 
 1872       , option [] ["doc-index-file"]
 1873           "A central index of haddock API documentation (template cannot use $pkgid)"
 1874           installHaddockIndex (\v flags -> flags { installHaddockIndex = v })
 1875           (reqArg' "TEMPLATE" (toFlag.toPathTemplate)
 1876                               (flagToList . fmap fromPathTemplate))
 1877 
 1878       , option [] ["dry-run"]
 1879           "Do not install anything, only print what would be installed."
 1880           installDryRun (\v flags -> flags { installDryRun = v })
 1881           trueArg
 1882 
 1883       , option [] ["only-download"]
 1884           "Do not build anything, only fetch the packages."
 1885           installOnlyDownload (\v flags -> flags { installOnlyDownload = v })
 1886           trueArg
 1887 
 1888       , option "" ["target-package-db"]
 1889          "package database to install into. Required when using ${pkgroot} prefix."
 1890          installDest (\v flags -> flags { installDest = v })
 1891          (reqArg "DATABASE" (succeedReadE (Flag . Cabal.CopyToDb))
 1892                             (\f -> case f of Flag (Cabal.CopyToDb p) -> [p]; _ -> []))
 1893       ] ++
 1894 
 1895       optionSolverFlags showOrParseArgs
 1896                         installMaxBackjumps     (\v flags -> flags { installMaxBackjumps     = v })
 1897                         installReorderGoals     (\v flags -> flags { installReorderGoals     = v })
 1898                         installCountConflicts   (\v flags -> flags { installCountConflicts   = v })
 1899                         installFineGrainedConflicts (\v flags -> flags { installFineGrainedConflicts = v })
 1900                         installMinimizeConflictSet (\v flags -> flags { installMinimizeConflictSet = v })
 1901                         installIndependentGoals (\v flags -> flags { installIndependentGoals = v })
 1902                         installShadowPkgs       (\v flags -> flags { installShadowPkgs       = v })
 1903                         installStrongFlags      (\v flags -> flags { installStrongFlags      = v })
 1904                         installAllowBootLibInstalls (\v flags -> flags { installAllowBootLibInstalls = v })
 1905                         installOnlyConstrained  (\v flags -> flags { installOnlyConstrained  = v }) ++
 1906 
 1907       [ option [] ["reinstall"]
 1908           "Install even if it means installing the same version again."
 1909           installReinstall (\v flags -> flags { installReinstall = v })
 1910           (yesNoOpt showOrParseArgs)
 1911 
 1912       , option [] ["avoid-reinstalls"]
 1913           "Do not select versions that would destructively overwrite installed packages."
 1914           (fmap asBool . installAvoidReinstalls)
 1915           (\v flags -> flags { installAvoidReinstalls = fmap AvoidReinstalls v })
 1916           (yesNoOpt showOrParseArgs)
 1917 
 1918       , option [] ["force-reinstalls"]
 1919           "Reinstall packages even if they will most likely break other installed packages."
 1920           installOverrideReinstall (\v flags -> flags { installOverrideReinstall = v })
 1921           (yesNoOpt showOrParseArgs)
 1922 
 1923       , option [] ["upgrade-dependencies"]
 1924           "Pick the latest version for all dependencies, rather than trying to pick an installed version."
 1925           installUpgradeDeps (\v flags -> flags { installUpgradeDeps = v })
 1926           (yesNoOpt showOrParseArgs)
 1927 
 1928       , option [] ["only-dependencies"]
 1929           "Install only the dependencies necessary to build the given packages"
 1930           installOnlyDeps (\v flags -> flags { installOnlyDeps = v })
 1931           (yesNoOpt showOrParseArgs)
 1932 
 1933       , option [] ["dependencies-only"]
 1934           "A synonym for --only-dependencies"
 1935           installOnlyDeps (\v flags -> flags { installOnlyDeps = v })
 1936           (yesNoOpt showOrParseArgs)
 1937 
 1938       , option [] ["index-state"]
 1939           ("Use source package index state as it existed at a previous time. " ++
 1940            "Accepts unix-timestamps (e.g. '@1474732068'), ISO8601 UTC timestamps " ++
 1941            "(e.g. '2016-09-24T17:47:48Z'), or 'HEAD' (default: 'HEAD').")
 1942           installIndexState (\v flags -> flags { installIndexState = v })
 1943           (reqArg "STATE" (parsecToReadE (const $ "index-state must be a  " ++
 1944                                        "unix-timestamps (e.g. '@1474732068'), " ++
 1945                                        "a ISO8601 UTC timestamp " ++
 1946                                        "(e.g. '2016-09-24T17:47:48Z'), or 'HEAD'")
 1947                                       (toFlag `fmap` parsec))
 1948                           (flagToList . fmap prettyShow))
 1949 
 1950       , option [] ["root-cmd"]
 1951           "(No longer supported, do not use.)"
 1952           installRootCmd (\v flags -> flags { installRootCmd = v })
 1953           (reqArg' "COMMAND" toFlag flagToList)
 1954 
 1955       , option [] ["symlink-bindir"]
 1956           "Add symlinks to installed executables into this directory."
 1957            installSymlinkBinDir (\v flags -> flags { installSymlinkBinDir = v })
 1958            (reqArgFlag "DIR")
 1959 
 1960       , option [] ["build-summary"]
 1961           "Save build summaries to file (name template can use $pkgid, $compiler, $os, $arch)"
 1962           installSummaryFile (\v flags -> flags { installSummaryFile = v })
 1963           (reqArg' "TEMPLATE" (\x -> toNubList [toPathTemplate x]) (map fromPathTemplate . fromNubList))
 1964 
 1965       , option [] ["build-log"]
 1966           "Log all builds to file (name template can use $pkgid, $compiler, $os, $arch)"
 1967           installLogFile (\v flags -> flags { installLogFile = v })
 1968           (reqArg' "TEMPLATE" (toFlag.toPathTemplate)
 1969                               (flagToList . fmap fromPathTemplate))
 1970 
 1971       , option [] ["remote-build-reporting"]
 1972           "Generate build reports to send to a remote server (none, anonymous or detailed)."
 1973           installBuildReports (\v flags -> flags { installBuildReports = v })
 1974           (reqArg "LEVEL" (parsecToReadE (const $ "report level must be 'none', "
 1975                                             ++ "'anonymous' or 'detailed'")
 1976                                       (toFlag `fmap` parsec))
 1977                           (flagToList . fmap prettyShow))
 1978 
 1979       , option [] ["report-planning-failure"]
 1980           "Generate build reports when the dependency solver fails. This is used by the Hackage build bot."
 1981           installReportPlanningFailure (\v flags -> flags { installReportPlanningFailure = v })
 1982           trueArg
 1983 
 1984       , option "" ["per-component"]
 1985           "Per-component builds when possible"
 1986           installPerComponent (\v flags -> flags { installPerComponent = v })
 1987           (boolOpt [] [])
 1988 
 1989       , option [] ["one-shot"]
 1990           "Do not record the packages in the world file."
 1991           installOneShot (\v flags -> flags { installOneShot = v })
 1992           (yesNoOpt showOrParseArgs)
 1993 
 1994       , option [] ["run-tests"]
 1995           "Run package test suites during installation."
 1996           installRunTests (\v flags -> flags { installRunTests = v })
 1997           trueArg
 1998 
 1999       , optionNumJobs
 2000         installNumJobs (\v flags -> flags { installNumJobs = v })
 2001 
 2002       , option [] ["keep-going"]
 2003           "After a build failure, continue to build other unaffected packages."
 2004           installKeepGoing (\v flags -> flags { installKeepGoing = v })
 2005           trueArg
 2006 
 2007       , option [] ["offline"]
 2008           "Don't download packages from the Internet."
 2009           installOfflineMode (\v flags -> flags { installOfflineMode = v })
 2010           (yesNoOpt showOrParseArgs)
 2011 
 2012       ] ++ case showOrParseArgs of      -- TODO: remove when "cabal install"
 2013                                         -- avoids
 2014           ParseArgs ->
 2015             [ option [] ["only"]
 2016               "Only installs the package in the current directory."
 2017               installOnly (\v flags -> flags { installOnly = v })
 2018               trueArg ]
 2019           _ -> []
 2020 
 2021 
 2022 instance Monoid InstallFlags where
 2023   mempty = gmempty
 2024   mappend = (<>)
 2025 
 2026 instance Semigroup InstallFlags where
 2027   (<>) = gmappend
 2028 
 2029 -- ------------------------------------------------------------
 2030 -- * Upload flags
 2031 -- ------------------------------------------------------------
 2032 
 2033 -- | Is this a candidate package or a package to be published?
 2034 data IsCandidate = IsCandidate | IsPublished
 2035                  deriving Eq
 2036 
 2037 data UploadFlags = UploadFlags {
 2038     uploadCandidate   :: Flag IsCandidate,
 2039     uploadDoc         :: Flag Bool,
 2040     uploadUsername    :: Flag Username,
 2041     uploadPassword    :: Flag Password,
 2042     uploadPasswordCmd :: Flag [String],
 2043     uploadVerbosity   :: Flag Verbosity
 2044   } deriving Generic
 2045 
 2046 defaultUploadFlags :: UploadFlags
 2047 defaultUploadFlags = UploadFlags {
 2048     uploadCandidate   = toFlag IsCandidate,
 2049     uploadDoc         = toFlag False,
 2050     uploadUsername    = mempty,
 2051     uploadPassword    = mempty,
 2052     uploadPasswordCmd = mempty,
 2053     uploadVerbosity   = toFlag normal
 2054   }
 2055 
 2056 uploadCommand :: CommandUI UploadFlags
 2057 uploadCommand = CommandUI {
 2058     commandName         = "upload",
 2059     commandSynopsis     = "Uploads source packages or documentation to Hackage.",
 2060     commandDescription  = Nothing,
 2061     commandNotes        = Just $ \_ ->
 2062          "You can store your Hackage login in the ~/.cabal/config file\n"
 2063       ++ relevantConfigValuesText ["username", "password", "password-command"],
 2064     commandUsage        = \pname ->
 2065          "Usage: " ++ pname ++ " upload [FLAGS] TARFILES\n",
 2066     commandDefaultFlags = defaultUploadFlags,
 2067     commandOptions      = \_ ->
 2068       [optionVerbosity uploadVerbosity
 2069        (\v flags -> flags { uploadVerbosity = v })
 2070 
 2071       ,option [] ["publish"]
 2072         "Publish the package instead of uploading it as a candidate."
 2073         uploadCandidate (\v flags -> flags { uploadCandidate = v })
 2074         (noArg (Flag IsPublished))
 2075 
 2076       ,option ['d'] ["documentation"]
 2077         ("Upload documentation instead of a source package. "
 2078         ++ "By default, this uploads documentation for a package candidate. "
 2079         ++ "To upload documentation for "
 2080         ++ "a published package, combine with --publish.")
 2081         uploadDoc (\v flags -> flags { uploadDoc = v })
 2082         trueArg
 2083 
 2084       ,option ['u'] ["username"]
 2085         "Hackage username."
 2086         uploadUsername (\v flags -> flags { uploadUsername = v })
 2087         (reqArg' "USERNAME" (toFlag . Username)
 2088                             (flagToList . fmap unUsername))
 2089 
 2090       ,option ['p'] ["password"]
 2091         "Hackage password."
 2092         uploadPassword (\v flags -> flags { uploadPassword = v })
 2093         (reqArg' "PASSWORD" (toFlag . Password)
 2094                             (flagToList . fmap unPassword))
 2095 
 2096       ,option ['P'] ["password-command"]
 2097         "Command to get Hackage password."
 2098         uploadPasswordCmd (\v flags -> flags { uploadPasswordCmd = v })
 2099         (reqArg' "PASSWORD" (Flag . words) (fromMaybe [] . flagToMaybe))
 2100       ]
 2101   }
 2102 
 2103 instance Monoid UploadFlags where
 2104   mempty = gmempty
 2105   mappend = (<>)
 2106 
 2107 instance Semigroup UploadFlags where
 2108   (<>) = gmappend
 2109 
 2110 -- ------------------------------------------------------------
 2111 -- * Init flags
 2112 -- ------------------------------------------------------------
 2113 
 2114 initCommand :: CommandUI IT.InitFlags
 2115 initCommand = CommandUI {
 2116     commandName = "init",
 2117     commandSynopsis = "Create a new .cabal package file.",
 2118     commandDescription = Just $ \_ -> wrapText $
 2119          "Create a .cabal, Setup.hs, and optionally a LICENSE file.\n"
 2120       ++ "\n"
 2121       ++ "Calling init with no arguments creates an executable, "
 2122       ++ "guessing as many options as possible. The interactive "
 2123       ++ "mode can be invoked by the -i/--interactive flag, which "
 2124       ++ "will try to guess as much as possible and prompt you for "
 2125       ++ "the rest. You can change init to always be interactive by "
 2126       ++ "setting the interactive flag in your configuration file. "
 2127       ++ "Command-line arguments are provided for scripting purposes.\n",
 2128     commandNotes = Nothing,
 2129     commandUsage = \pname ->
 2130          "Usage: " ++ pname ++ " init [FLAGS]\n",
 2131     commandDefaultFlags = IT.defaultInitFlags,
 2132     commandOptions = initOptions
 2133   }
 2134 
 2135 initOptions :: ShowOrParseArgs -> [OptionField IT.InitFlags]
 2136 initOptions _ =
 2137   [ option ['i'] ["interactive"]
 2138     "interactive mode."
 2139     IT.interactive (\v flags -> flags { IT.interactive = v })
 2140     (boolOpt' (['i'], ["interactive"]) (['n'], ["non-interactive"]))
 2141 
 2142   , option ['q'] ["quiet"]
 2143     "Do not generate log messages to stdout."
 2144     IT.quiet (\v flags -> flags { IT.quiet = v })
 2145     trueArg
 2146 
 2147   , option [] ["no-comments"]
 2148     "Do not generate explanatory comments in the .cabal file."
 2149     IT.noComments (\v flags -> flags { IT.noComments = v })
 2150     trueArg
 2151 
 2152   , option ['m'] ["minimal"]
 2153     "Generate a minimal .cabal file, that is, do not include extra empty fields.  Also implies --no-comments."
 2154     IT.minimal (\v flags -> flags { IT.minimal = v })
 2155     trueArg
 2156 
 2157   , option [] ["overwrite"]
 2158     "Overwrite any existing .cabal, LICENSE, or Setup.hs files without warning."
 2159     IT.overwrite (\v flags -> flags { IT.overwrite = v })
 2160     trueArg
 2161 
 2162   , option [] ["package-dir", "packagedir"]
 2163     "Root directory of the package (default = current directory)."
 2164     IT.packageDir (\v flags -> flags { IT.packageDir = v })
 2165     (reqArgFlag "DIRECTORY")
 2166 
 2167   , option ['p'] ["package-name"]
 2168     "Name of the Cabal package to create."
 2169     IT.packageName (\v flags -> flags { IT.packageName = v })
 2170     (reqArg "PACKAGE" (parsecToReadE ("Cannot parse package name: "++)
 2171                                   (toFlag `fmap` parsec))
 2172                       (flagToList . fmap prettyShow))
 2173 
 2174   , option [] ["version"]
 2175     "Initial version of the package."
 2176     IT.version (\v flags -> flags { IT.version = v })
 2177     (reqArg "VERSION" (parsecToReadE ("Cannot parse package version: "++)
 2178                                   (toFlag `fmap` parsec))
 2179                       (flagToList . fmap prettyShow))
 2180 
 2181   , option [] ["cabal-version"]
 2182     "Version of the Cabal specification."
 2183     IT.cabalVersion (\v flags -> flags { IT.cabalVersion = v })
 2184     (reqArg "CABALSPECVERSION" (parsecToReadE ("Cannot parse Cabal specification version: "++)
 2185                                         (fmap (toFlag . getSpecVersion) parsec))
 2186                             (flagToList . fmap (prettyShow . SpecVersion)))
 2187 
 2188   , option ['l'] ["license"]
 2189     "Project license."
 2190     IT.license (\v flags -> flags { IT.license = v })
 2191     (reqArg "LICENSE" (parsecToReadE ("Cannot parse license: "++)
 2192                                   (toFlag `fmap` parsec))
 2193                       (flagToList . fmap prettyShow))
 2194 
 2195   , option ['a'] ["author"]
 2196     "Name of the project's author."
 2197     IT.author (\v flags -> flags { IT.author = v })
 2198     (reqArgFlag "NAME")
 2199 
 2200   , option ['e'] ["email"]
 2201     "Email address of the maintainer."
 2202     IT.email (\v flags -> flags { IT.email = v })
 2203     (reqArgFlag "EMAIL")
 2204 
 2205   , option ['u'] ["homepage"]
 2206     "Project homepage and/or repository."
 2207     IT.homepage (\v flags -> flags { IT.homepage = v })
 2208     (reqArgFlag "URL")
 2209 
 2210   , option ['s'] ["synopsis"]
 2211     "Short project synopsis."
 2212     IT.synopsis (\v flags -> flags { IT.synopsis = v })
 2213     (reqArgFlag "TEXT")
 2214 
 2215   , option ['c'] ["category"]
 2216     "Project category."
 2217     IT.category (\v flags -> flags { IT.category = v })
 2218     (reqArg' "CATEGORY" (\s -> toFlag $ maybe (Left s) Right (readMaybe s))
 2219                         (flagToList . fmap (either id show)))
 2220 
 2221   , option ['x'] ["extra-source-file"]
 2222     "Extra source file to be distributed with tarball."
 2223     IT.extraSrc (\v flags -> flags { IT.extraSrc = v })
 2224     (reqArg' "FILE" (Just . (:[]))
 2225                     (fromMaybe []))
 2226 
 2227   , option [] ["lib", "is-library"]
 2228     "Build a library."
 2229     IT.packageType (\v flags -> flags { IT.packageType = v })
 2230     (noArg (Flag IT.Library))
 2231 
 2232   , option [] ["exe", "is-executable"]
 2233     "Build an executable."
 2234     IT.packageType
 2235     (\v flags -> flags { IT.packageType = v })
 2236     (noArg (Flag IT.Executable))
 2237 
 2238     , option [] ["libandexe", "is-libandexe"]
 2239     "Build a library and an executable."
 2240     IT.packageType
 2241     (\v flags -> flags { IT.packageType = v })
 2242     (noArg (Flag IT.LibraryAndExecutable))
 2243 
 2244       , option [] ["tests"]
 2245         "Generate a test suite for the library."
 2246         IT.initializeTestSuite
 2247         (\v flags -> flags { IT.initializeTestSuite = v })
 2248         trueArg
 2249 
 2250       , option [] ["test-dir"]
 2251         "Directory containing tests."
 2252         IT.testDirs (\v flags -> flags { IT.testDirs = v })
 2253         (reqArg' "DIR" (Just . (:[]))
 2254                        (fromMaybe []))
 2255 
 2256   , option [] ["simple"]
 2257     "Create a simple project with sensible defaults."
 2258     IT.simpleProject
 2259     (\v flags -> flags { IT.simpleProject = v })
 2260     trueArg
 2261 
 2262   , option [] ["main-is"]
 2263     "Specify the main module."
 2264     IT.mainIs
 2265     (\v flags -> flags { IT.mainIs = v })
 2266     (reqArgFlag "FILE")
 2267 
 2268   , option [] ["language"]
 2269     "Specify the default language."
 2270     IT.language
 2271     (\v flags -> flags { IT.language = v })
 2272     (reqArg "LANGUAGE" (parsecToReadE ("Cannot parse language: "++)
 2273                                    (toFlag `fmap` parsec))
 2274                       (flagToList . fmap prettyShow))
 2275 
 2276   , option ['o'] ["expose-module"]
 2277     "Export a module from the package."
 2278     IT.exposedModules
 2279     (\v flags -> flags { IT.exposedModules = v })
 2280     (reqArg "MODULE" (parsecToReadE ("Cannot parse module name: "++)
 2281                                  ((Just . (:[])) `fmap` parsec))
 2282                      (maybe [] (fmap prettyShow)))
 2283 
 2284   , option [] ["extension"]
 2285     "Use a LANGUAGE extension (in the other-extensions field)."
 2286     IT.otherExts
 2287     (\v flags -> flags { IT.otherExts = v })
 2288     (reqArg "EXTENSION" (parsecToReadE ("Cannot parse extension: "++)
 2289                                     ((Just . (:[])) `fmap` parsec))
 2290                         (maybe [] (fmap prettyShow)))
 2291 
 2292   , option ['d'] ["dependency"]
 2293     "Package dependency."
 2294     IT.dependencies (\v flags -> flags { IT.dependencies = v })
 2295     (reqArg "PACKAGE" (parsecToReadE ("Cannot parse dependency: "++)
 2296                                   ((Just . (:[])) `fmap` parsec))
 2297                       (maybe [] (fmap prettyShow)))
 2298 
 2299   , option [] ["application-dir"]
 2300     "Directory containing package application executable."
 2301     IT.applicationDirs (\v flags -> flags { IT.applicationDirs = v})
 2302     (reqArg' "DIR" (Just . (:[]))
 2303                    (fromMaybe []))
 2304 
 2305   , option [] ["source-dir", "sourcedir"]
 2306     "Directory containing package library source."
 2307     IT.sourceDirs (\v flags -> flags { IT.sourceDirs = v })
 2308     (reqArg' "DIR" (Just . (:[]))
 2309                    (fromMaybe []))
 2310 
 2311   , option [] ["build-tool"]
 2312     "Required external build tool."
 2313     IT.buildTools (\v flags -> flags { IT.buildTools = v })
 2314     (reqArg' "TOOL" (Just . (:[]))
 2315                     (fromMaybe []))
 2316 
 2317     -- NB: this is a bit of a transitional hack and will likely be
 2318     -- removed again if `cabal init` is migrated to the v2-* command
 2319     -- framework
 2320   , option "w" ["with-compiler"]
 2321     "give the path to a particular compiler"
 2322     IT.initHcPath (\v flags -> flags { IT.initHcPath = v })
 2323     (reqArgFlag "PATH")
 2324 
 2325   , optionVerbosity IT.initVerbosity (\v flags -> flags { IT.initVerbosity = v })
 2326   ]
 2327 
 2328 -- ------------------------------------------------------------
 2329 -- * Copy and Register
 2330 -- ------------------------------------------------------------
 2331 
 2332 copyCommand :: CommandUI CopyFlags
 2333 copyCommand = Cabal.copyCommand
 2334  { commandNotes = Just $ \pname ->
 2335     "Examples:\n"
 2336      ++ "  " ++ pname ++ " v1-copy           "
 2337      ++ "    All the components in the package\n"
 2338      ++ "  " ++ pname ++ " v1-copy foo       "
 2339      ++ "    A component (i.e. lib, exe, test suite)"
 2340   , commandUsage = usageAlternatives "v1-copy" $
 2341     [ "[FLAGS]"
 2342     , "COMPONENTS [FLAGS]"
 2343     ]
 2344  }
 2345 
 2346 registerCommand :: CommandUI RegisterFlags
 2347 registerCommand = Cabal.registerCommand
 2348  { commandUsage = \pname ->  "Usage: " ++ pname ++ " v1-register [FLAGS]\n" }
 2349 
 2350 -- ------------------------------------------------------------
 2351 -- * ActAsSetup flags
 2352 -- ------------------------------------------------------------
 2353 
 2354 data ActAsSetupFlags = ActAsSetupFlags {
 2355     actAsSetupBuildType :: Flag BuildType
 2356 } deriving Generic
 2357 
 2358 defaultActAsSetupFlags :: ActAsSetupFlags
 2359 defaultActAsSetupFlags = ActAsSetupFlags {
 2360     actAsSetupBuildType = toFlag Simple
 2361 }
 2362 
 2363 actAsSetupCommand :: CommandUI ActAsSetupFlags
 2364 actAsSetupCommand = CommandUI {
 2365   commandName         = "act-as-setup",
 2366   commandSynopsis     = "Run as-if this was a Setup.hs",
 2367   commandDescription  = Nothing,
 2368   commandNotes        = Nothing,
 2369   commandUsage        = \pname ->
 2370     "Usage: " ++ pname ++ " act-as-setup\n",
 2371   commandDefaultFlags = defaultActAsSetupFlags,
 2372   commandOptions      = \_ ->
 2373       [option "" ["build-type"]
 2374          "Use the given build type."
 2375          actAsSetupBuildType (\v flags -> flags { actAsSetupBuildType = v })
 2376          (reqArg "BUILD-TYPE" (parsecToReadE ("Cannot parse build type: "++)
 2377                                (fmap toFlag parsec))
 2378                               (map prettyShow . flagToList))
 2379       ]
 2380 }
 2381 
 2382 instance Monoid ActAsSetupFlags where
 2383   mempty = gmempty
 2384   mappend = (<>)
 2385 
 2386 instance Semigroup ActAsSetupFlags where
 2387   (<>) = gmappend
 2388 
 2389 -- ------------------------------------------------------------
 2390 -- * UserConfig flags
 2391 -- ------------------------------------------------------------
 2392 
 2393 data UserConfigFlags = UserConfigFlags {
 2394   userConfigVerbosity   :: Flag Verbosity,
 2395   userConfigForce       :: Flag Bool,
 2396   userConfigAppendLines :: Flag [String]
 2397   } deriving Generic
 2398 
 2399 instance Monoid UserConfigFlags where
 2400   mempty = UserConfigFlags {
 2401     userConfigVerbosity   = toFlag normal,
 2402     userConfigForce       = toFlag False,
 2403     userConfigAppendLines = toFlag []
 2404     }
 2405   mappend = (<>)
 2406 
 2407 instance Semigroup UserConfigFlags where
 2408   (<>) = gmappend
 2409 
 2410 userConfigCommand :: CommandUI UserConfigFlags
 2411 userConfigCommand = CommandUI {
 2412   commandName         = "user-config",
 2413   commandSynopsis     = "Display and update the user's global cabal configuration.",
 2414   commandDescription  = Just $ \_ -> wrapText $
 2415        "When upgrading cabal, the set of configuration keys and their default"
 2416     ++ " values may change. This command provides means to merge the existing"
 2417     ++ " config in ~/.cabal/config"
 2418     ++ " (i.e. all bindings that are actually defined and not commented out)"
 2419     ++ " and the default config of the new version.\n"
 2420     ++ "\n"
 2421     ++ "init: Creates a new config file at either ~/.cabal/config or as"
 2422     ++ " specified by --config-file, if given. An existing file won't be "
 2423     ++ " overwritten unless -f or --force is given.\n"
 2424     ++ "diff: Shows a pseudo-diff of the user's ~/.cabal/config file and"
 2425     ++ " the default configuration that would be created by cabal if the"
 2426     ++ " config file did not exist.\n"
 2427     ++ "update: Applies the pseudo-diff to the configuration that would be"
 2428     ++ " created by default, and write the result back to ~/.cabal/config.",
 2429 
 2430   commandNotes        = Nothing,
 2431   commandUsage        = usageAlternatives "user-config" ["init", "diff", "update"],
 2432   commandDefaultFlags = mempty,
 2433   commandOptions      = \ _ -> [
 2434    optionVerbosity userConfigVerbosity (\v flags -> flags { userConfigVerbosity = v })
 2435  , option ['f'] ["force"]
 2436      "Overwrite the config file if it already exists."
 2437      userConfigForce (\v flags -> flags { userConfigForce = v })
 2438      trueArg
 2439  , option ['a'] ["augment"]
 2440      "Additional setting to augment the config file (replacing a previous setting if it existed)."
 2441      userConfigAppendLines (\v flags -> flags
 2442                                {userConfigAppendLines =
 2443                                    Flag $ concat (flagToList (userConfigAppendLines flags) ++ flagToList v)})
 2444      (reqArg' "CONFIGLINE" (Flag . (:[])) (fromMaybe [] . flagToMaybe))
 2445    ]
 2446   }
 2447 
 2448 
 2449 -- ------------------------------------------------------------
 2450 -- * GetOpt Utils
 2451 -- ------------------------------------------------------------
 2452 
 2453 reqArgFlag :: ArgPlaceHolder ->
 2454               MkOptDescr (b -> Flag String) (Flag String -> b -> b) b
 2455 reqArgFlag ad = reqArg ad (succeedReadE Flag) flagToList
 2456 
 2457 liftOptions :: (b -> a) -> (a -> b -> b)
 2458             -> [OptionField a] -> [OptionField b]
 2459 liftOptions get set = map (liftOption get set)
 2460 
 2461 yesNoOpt :: ShowOrParseArgs -> MkOptDescr (b -> Flag Bool) (Flag Bool -> b -> b) b
 2462 yesNoOpt ShowArgs sf lf = trueArg sf lf
 2463 yesNoOpt _        sf lf = Command.boolOpt' flagToMaybe Flag (sf, lf) ([], map ("no-" ++) lf) sf lf
 2464 
 2465 optionSolver :: (flags -> Flag PreSolver)
 2466              -> (Flag PreSolver -> flags -> flags)
 2467              -> OptionField flags
 2468 optionSolver get set =
 2469   option [] ["solver"]
 2470     ("Select dependency solver to use (default: " ++ prettyShow defaultSolver ++ "). Choices: " ++ allSolvers ++ ".")
 2471     get set
 2472     (reqArg "SOLVER" (parsecToReadE (const $ "solver must be one of: " ++ allSolvers)
 2473                                     (toFlag `fmap` parsec))
 2474                      (flagToList . fmap prettyShow))
 2475 
 2476 optionSolverFlags :: ShowOrParseArgs
 2477                   -> (flags -> Flag Int   ) -> (Flag Int    -> flags -> flags)
 2478                   -> (flags -> Flag ReorderGoals)     -> (Flag ReorderGoals     -> flags -> flags)
 2479                   -> (flags -> Flag CountConflicts)   -> (Flag CountConflicts   -> flags -> flags)
 2480                   -> (flags -> Flag FineGrainedConflicts) -> (Flag FineGrainedConflicts -> flags -> flags)
 2481                   -> (flags -> Flag MinimizeConflictSet) -> (Flag MinimizeConflictSet -> flags -> flags)
 2482                   -> (flags -> Flag IndependentGoals) -> (Flag IndependentGoals -> flags -> flags)
 2483                   -> (flags -> Flag ShadowPkgs)       -> (Flag ShadowPkgs       -> flags -> flags)
 2484                   -> (flags -> Flag StrongFlags)      -> (Flag StrongFlags      -> flags -> flags)
 2485                   -> (flags -> Flag AllowBootLibInstalls) -> (Flag AllowBootLibInstalls -> flags -> flags)
 2486                   -> (flags -> Flag OnlyConstrained)  -> (Flag OnlyConstrained  -> flags -> flags)
 2487                   -> [OptionField flags]
 2488 optionSolverFlags showOrParseArgs getmbj setmbj getrg setrg getcc setcc
 2489                   getfgc setfgc getmc setmc getig setig getsip setsip
 2490                   getstrfl setstrfl getib setib getoc setoc =
 2491   [ option [] ["max-backjumps"]
 2492       ("Maximum number of backjumps allowed while solving (default: " ++ show defaultMaxBackjumps ++ "). Use a negative number to enable unlimited backtracking. Use 0 to disable backtracking completely.")
 2493       getmbj setmbj
 2494       (reqArg "NUM" (parsecToReadE ("Cannot parse number: "++) (fmap toFlag P.signedIntegral))
 2495                     (map show . flagToList))
 2496   , option [] ["reorder-goals"]
 2497       "Try to reorder goals according to certain heuristics. Slows things down on average, but may make backtracking faster for some packages."
 2498       (fmap asBool . getrg)
 2499       (setrg . fmap ReorderGoals)
 2500       (yesNoOpt showOrParseArgs)
 2501   , option [] ["count-conflicts"]
 2502       "Try to speed up solving by preferring goals that are involved in a lot of conflicts (default)."
 2503       (fmap asBool . getcc)
 2504       (setcc . fmap CountConflicts)
 2505       (yesNoOpt showOrParseArgs)
 2506   , option [] ["fine-grained-conflicts"]
 2507       "Skip a version of a package if it does not resolve the conflicts encountered in the last version, as a solver optimization (default)."
 2508       (fmap asBool . getfgc)
 2509       (setfgc . fmap FineGrainedConflicts)
 2510       (yesNoOpt showOrParseArgs)
 2511   , option [] ["minimize-conflict-set"]
 2512       ("When there is no solution, try to improve the error message by finding "
 2513         ++ "a minimal conflict set (default: false). May increase run time "
 2514         ++ "significantly.")
 2515       (fmap asBool . getmc)
 2516       (setmc . fmap MinimizeConflictSet)
 2517       (yesNoOpt showOrParseArgs)
 2518   , option [] ["independent-goals"]
 2519       "Treat several goals on the command line as independent. If several goals depend on the same package, different versions can be chosen."
 2520       (fmap asBool . getig)
 2521       (setig . fmap IndependentGoals)
 2522       (yesNoOpt showOrParseArgs)
 2523   , option [] ["shadow-installed-packages"]
 2524       "If multiple package instances of the same version are installed, treat all but one as shadowed."
 2525       (fmap asBool . getsip)
 2526       (setsip . fmap ShadowPkgs)
 2527       (yesNoOpt showOrParseArgs)
 2528   , option [] ["strong-flags"]
 2529       "Do not defer flag choices (this used to be the default in cabal-install <= 1.20)."
 2530       (fmap asBool . getstrfl)
 2531       (setstrfl . fmap StrongFlags)
 2532       (yesNoOpt showOrParseArgs)
 2533   , option [] ["allow-boot-library-installs"]
 2534       "Allow cabal to install base, ghc-prim, integer-simple, integer-gmp, and template-haskell."
 2535       (fmap asBool . getib)
 2536       (setib . fmap AllowBootLibInstalls)
 2537       (yesNoOpt showOrParseArgs)
 2538   , option [] ["reject-unconstrained-dependencies"]
 2539       "Require these packages to have constraints on them if they are to be selected (default: none)."
 2540       getoc
 2541       setoc
 2542       (reqArg "none|all"
 2543          (parsecToReadE
 2544             (const "reject-unconstrained-dependencies must be 'none' or 'all'")
 2545             (toFlag `fmap` parsec))
 2546          (flagToList . fmap prettyShow))
 2547 
 2548   ]
 2549 
 2550 usagePackages :: String -> String -> String
 2551 usagePackages name pname =
 2552      "Usage: " ++ pname ++ " " ++ name ++ " [PACKAGES]\n"
 2553 
 2554 usageFlags :: String -> String -> String
 2555 usageFlags name pname =
 2556   "Usage: " ++ pname ++ " " ++ name ++ " [FLAGS]\n"
 2557 
 2558 -- ------------------------------------------------------------
 2559 -- * Repo helpers
 2560 -- ------------------------------------------------------------
 2561 
 2562 showRemoteRepo :: RemoteRepo -> String
 2563 showRemoteRepo = prettyShow
 2564 
 2565 readRemoteRepo :: String -> Maybe RemoteRepo
 2566 readRemoteRepo = simpleParsec
 2567 
 2568 showLocalRepo :: LocalRepo -> String
 2569 showLocalRepo = prettyShow
 2570 
 2571 readLocalRepo :: String -> Maybe LocalRepo
 2572 readLocalRepo = simpleParsec
 2573 
 2574 -- ------------------------------------------------------------
 2575 -- * Helpers for Documentation
 2576 -- ------------------------------------------------------------
 2577 
 2578 relevantConfigValuesText :: [String] -> String
 2579 relevantConfigValuesText vs =
 2580      "Relevant global configuration keys:\n"
 2581   ++ concat ["  " ++ v ++ "\n" |v <- vs]