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