Skip to content

Commit

Permalink
Add a cabal target command
Browse files Browse the repository at this point in the history
- Avoid list in the help
- Use establishProjectBaseContext
- Remove withContextAndSelectors
- Use rebuildInstallPlan and resolveTargets
- Extract targetForms
- Satisfy hlint
- Remove unnecessary do
- Use safeHead
- Call printPlanTargetForms for everything
- Remove planTargetForms
- Rework command description
- Remove script as a possible TARGET form
- Section help into; intro, targetFroms and ctypes
- Use pretty printing for examples
- Short form and long form
- Add a changelog entry
- Need nixStyleOptions for cabal-testsuite
  - unrecognized 'v2-target' option `-vverbose +markoutput +nowrap'
  - unrecognized 'v2-target' option `--builddir'
  - unrecognized 'v2-target' option `-j1'
- Use notice so target forms are marked output
- Add tests of target all, implicit and explicit
- Add tests of all:exes and all:tests
- Add test of all:benches
- Add tests with --enable-tests and --enable-benchmarks
- Warn that package targets display libs and exes
- Add package target tests
- Add path target tests
- Add component target tests
- Add c package with only a library
- Add tests for missing ctypes
- Exclude new-target from other commands
- Move target command to configuration group
- Add target command docs
- Add cabal target docs
- A significant change
- Drop cleans from tests
- Use noticeDoc to preserve indent
- Satisfy fourmolu
- Show the number of matches found matching query
- Change synopsis of command, target verb
- Remove disclosed, use show, WARN and NOTE
- Typo command singular
- Bring the command docs inline with --help docs
- Remove disclosing from changelog
- Only by default, not *only*.

Co-Authored-By: brandon s allbery kf8nh <[email protected]>
  • Loading branch information
philderbeast and geekosaur committed Jan 14, 2025
1 parent dcdbeb0 commit f1fbee2
Show file tree
Hide file tree
Showing 28 changed files with 659 additions and 2 deletions.
1 change: 1 addition & 0 deletions cabal-install/cabal-install.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -110,6 +110,7 @@ library
Distribution.Client.CmdRepl
Distribution.Client.CmdRun
Distribution.Client.CmdSdist
Distribution.Client.CmdTarget
Distribution.Client.CmdTest
Distribution.Client.CmdUpdate
Distribution.Client.Compat.Directory
Expand Down
224 changes: 224 additions & 0 deletions cabal-install/src/Distribution/Client/CmdTarget.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,224 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Distribution.Client.CmdTarget
( targetCommand
, targetAction
) where

import Distribution.Client.Compat.Prelude
import Prelude ()

import qualified Data.Map as Map
import Distribution.Client.CmdBuild (selectComponentTarget, selectPackageTargets)
import Distribution.Client.CmdErrorMessages
import Distribution.Client.InstallPlan
import qualified Distribution.Client.InstallPlan as InstallPlan
import Distribution.Client.NixStyleOptions
( NixStyleFlags (..)
, defaultNixStyleFlags
, nixStyleOptions
)
import Distribution.Client.ProjectOrchestration
import Distribution.Client.ProjectPlanning
import Distribution.Client.Setup
( ConfigFlags (..)
, GlobalFlags
)
import Distribution.Client.TargetProblem
( TargetProblem'
)
import Distribution.Package
import Distribution.Simple.Command
( CommandUI (..)
, usageAlternatives
)
import Distribution.Simple.Flag (fromFlagOrDefault)
import Distribution.Simple.Utils
( noticeDoc
, safeHead
, wrapText
)
import Distribution.Verbosity
( normal
)
import Text.PrettyPrint
import qualified Text.PrettyPrint as Pretty

-------------------------------------------------------------------------------
-- Command
-------------------------------------------------------------------------------

targetCommand :: CommandUI (NixStyleFlags ())
targetCommand =
CommandUI
{ commandName = "v2-target"
, commandSynopsis = "Target a subset of all targets."
, commandUsage = usageAlternatives "v2-target" ["[TARGETS]"]
, commandDescription =
Just . const . render $
vcat
[ intro
, vcat $ punctuate (text "\n") [targetForms, ctypes, Pretty.empty]
, caution
, unique
]
, commandNotes = Just $ \pname -> render $ examples pname
, commandDefaultFlags = defaultNixStyleFlags ()
, commandOptions = nixStyleOptions (const [])
}
where
intro =
text . wrapText $
"Discover targets in a project for use with other commands taking [TARGETS].\n\n"
++ "This command, like many others, takes [TARGETS]. Taken together, these will"
++ " select for a set of targets in the project. When none are supplied, the"
++ " command acts as if 'all' was supplied."
++ " Targets in the returned subset are shown sorted and fully-qualified."

targetForms =
vcat
[ text "A [TARGETS] item can be one of these target forms:"
, nest 1 . vcat $
(char '-' <+>)
<$> [ text "a package target (e.g. [pkg:]package)"
, text "a component target (e.g. [package:][ctype:]component)"
, text "all packages (e.g. all)"
, text "components of a particular type (e.g. package:ctypes or all:ctypes)"
, text "a module target: (e.g. [package:][ctype:]module)"
, text "a filepath target: (e.g. [package:][ctype:]filepath)"
]
]

ctypes =
vcat
[ text "The ctypes, in short form and (long form), can be one of:"
, nest 1 . vcat $
(char '-' <+>)
<$> [ "libs" <+> parens "libraries"
, "exes" <+> parens "executables"
, "tests"
, "benches" <+> parens "benchmarks"
, "flibs" <+> parens "foreign-libraries"
]
]

caution =
text . wrapText $
"WARNING: For a package, all, module or filepath target, cabal target [TARGETS] \
\ will only show 'libs' and 'exes' of the [TARGETS] by default. To also show \
\ tests and benchmarks, enable them with '--enable-tests' and \
\ '--enable-benchmarks'."

unique =
text . wrapText $
"NOTE: For commands expecting a unique TARGET, a fully-qualified target is the safe \
\ way to go but it may be convenient to type out a shorter TARGET. For example, if the \
\ set of 'cabal target all:exes' has one item then 'cabal list-bin all:exes' will \
\ work too."

examples pname =
vcat
[ text "Examples" Pretty.<> colon
, nest 2 $
vcat
[ vcat
[ text pname <+> text "v2-target all"
, nest 2 $ text "Targets of the package in the current directory or all packages in the project"
]
, vcat
[ text pname <+> text "v2-target pkgname"
, nest 2 $ text "Targets of the package named pkgname in the project"
]
, vcat
[ text pname <+> text "v2-target ./pkgfoo"
, nest 2 $ text "Targets of the package in the ./pkgfoo directory"
]
, vcat
[ text pname <+> text "v2-target cname"
, nest 2 $ text "Targets of the component named cname in the project"
]
]
]

-------------------------------------------------------------------------------
-- Action
-------------------------------------------------------------------------------

targetAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO ()
targetAction flags@NixStyleFlags{..} ts globalFlags = do
ProjectBaseContext
{ distDirLayout
, cabalDirLayout
, projectConfig
, localPackages
} <-
establishProjectBaseContext verbosity cliConfig OtherCommand

(_, elaboratedPlan, _, _, _) <-
rebuildInstallPlan
verbosity
distDirLayout
cabalDirLayout
projectConfig
localPackages
Nothing

targetSelectors <-
either (reportTargetSelectorProblems verbosity) return
=<< readTargetSelectors localPackages Nothing targetStrings

targets :: TargetsMap <-
either (reportBuildTargetProblems verbosity) return $
resolveTargets
selectPackageTargets
selectComponentTarget
elaboratedPlan
Nothing
targetSelectors

printTargetForms verbosity targetStrings targets elaboratedPlan
where
verbosity = fromFlagOrDefault normal (configVerbosity configFlags)
targetStrings = if null ts then ["all"] else ts
cliConfig =
commandLineFlagsToProjectConfig
globalFlags
flags
mempty

reportBuildTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
reportBuildTargetProblems verbosity = reportTargetProblems verbosity "target"

printTargetForms :: Verbosity -> [String] -> TargetsMap -> ElaboratedInstallPlan -> IO ()
printTargetForms verbosity targetStrings targets elaboratedPlan =
noticeDoc verbosity $
vcat
[ text "Fully qualified target forms" Pretty.<> colon
, nest 1 $ vcat [text "-" <+> text tf | tf <- targetForms]
, found
]
where
found =
let n = length targets
t = if n == 1 then "target" else "targets"
query = intercalate ", " targetStrings
in text "Found" <+> int n <+> text t <+> text "matching" <+> text query Pretty.<> char '.'

localPkgs =
[x | Configured x@ElaboratedConfiguredPackage{elabLocalToProject = True} <- InstallPlan.toList elaboratedPlan]

targetForm ct x =
let pkgId@PackageIdentifier{pkgName = n} = elabPkgSourceId x
in render $ pretty n Pretty.<> colon Pretty.<> text (showComponentTarget pkgId ct)

targetForms =
sort $
catMaybes
[ targetForm ct <$> pkg
| (u :: UnitId, xs) <- Map.toAscList targets
, let pkg = safeHead $ filter ((== u) . elabUnitId) localPkgs
, (ct :: ComponentTarget, _) <- xs
]
2 changes: 2 additions & 0 deletions cabal-install/src/Distribution/Client/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,7 @@ import qualified Distribution.Client.CmdPath as CmdPath
import qualified Distribution.Client.CmdRepl as CmdRepl
import qualified Distribution.Client.CmdRun as CmdRun
import qualified Distribution.Client.CmdSdist as CmdSdist
import qualified Distribution.Client.CmdTarget as CmdTarget
import qualified Distribution.Client.CmdTest as CmdTest
import qualified Distribution.Client.CmdUpdate as CmdUpdate

Expand Down Expand Up @@ -460,6 +461,7 @@ mainWorker args = do
, newCmd CmdExec.execCommand CmdExec.execAction
, newCmd CmdClean.cleanCommand CmdClean.cleanAction
, newCmd CmdSdist.sdistCommand CmdSdist.sdistAction
, newCmd CmdTarget.targetCommand CmdTarget.targetAction
, legacyCmd configureExCommand configureAction
, legacyCmd buildCommand buildAction
, legacyCmd replCommand replAction
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -934,7 +934,6 @@ distinctTargetComponents targetsMap =

------------------------------------------------------------------------------
-- Displaying what we plan to do
--

-- | Print a user-oriented presentation of the install plan, indicating what
-- will be built.
Expand Down
7 changes: 6 additions & 1 deletion cabal-install/src/Distribution/Client/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -282,6 +282,7 @@ globalCommand commands =
, "unpack"
, "init"
, "configure"
, "target"
, "build"
, "clean"
, "run"
Expand All @@ -302,6 +303,7 @@ globalCommand commands =
, "path"
, "new-build"
, "new-configure"
, "new-target"
, "new-repl"
, "new-freeze"
, "new-run"
Expand Down Expand Up @@ -334,7 +336,8 @@ globalCommand commands =
, "v1-register"
, "v1-reconfigure"
, -- v2 commands, nix-style
"v2-build"
"v2-target"
, "v2-build"
, "v2-configure"
, "v2-repl"
, "v2-freeze"
Expand Down Expand Up @@ -379,6 +382,7 @@ globalCommand commands =
, addCmd "gen-bounds"
, addCmd "outdated"
, addCmd "path"
, addCmd "target"
, par
, startGroup "project building and installing"
, addCmd "build"
Expand Down Expand Up @@ -406,6 +410,7 @@ globalCommand commands =
, addCmd "hscolour"
, par
, startGroup "new-style projects (forwards-compatible aliases)"
, addCmd "v2-target"
, addCmd "v2-build"
, addCmd "v2-configure"
, addCmd "v2-repl"
Expand Down
8 changes: 8 additions & 0 deletions cabal-testsuite/PackageTests/Target/cabal.all-benches.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Resolving dependencies...
Fully qualified target forms:
- a:bench:a-bench
- b:bench:b-bench
Found 2 targets matching all:benches.
15 changes: 15 additions & 0 deletions cabal-testsuite/PackageTests/Target/cabal.all-enable-benches.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Resolving dependencies...
Fully qualified target forms:
- a:bench:a-bench
- a:exe:a-exe
- a:lib:a
- a:lib:a-sublib
- b:bench:b-bench
- b:exe:b-exe
- b:lib:b
- b:lib:b-sublib
- c:lib:c
Found 9 targets matching all.
15 changes: 15 additions & 0 deletions cabal-testsuite/PackageTests/Target/cabal.all-enable-tests.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Resolving dependencies...
Fully qualified target forms:
- a:exe:a-exe
- a:lib:a
- a:lib:a-sublib
- a:test:a-test
- b:exe:b-exe
- b:lib:b
- b:lib:b-sublib
- b:test:b-test
- c:lib:c
Found 9 targets matching all.
8 changes: 8 additions & 0 deletions cabal-testsuite/PackageTests/Target/cabal.all-exes.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Resolving dependencies...
Fully qualified target forms:
- a:exe:a-exe
- b:exe:b-exe
Found 2 targets matching all:exes.
8 changes: 8 additions & 0 deletions cabal-testsuite/PackageTests/Target/cabal.all-tests.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Resolving dependencies...
Fully qualified target forms:
- a:test:a-test
- b:test:b-test
Found 2 targets matching all:tests.
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Resolving dependencies...
Fully qualified target forms:
- a:bench:a-bench
Found 1 target matching a:bench:a-bench.
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Fully qualified target forms:
- a:bench:a-bench
Found 1 target matching bench:a-bench.
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Fully qualified target forms:
- a:bench:a-bench
Found 1 target matching a:a-bench.
19 changes: 19 additions & 0 deletions cabal-testsuite/PackageTests/Target/cabal.component-target-exe.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Resolving dependencies...
Fully qualified target forms:
- a:exe:a-exe
Found 1 target matching a:exe:a-exe.
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Fully qualified target forms:
- a:exe:a-exe
Found 1 target matching exe:a-exe.
# cabal v2-target
Configuration is affected by the following files:
- cabal.project
Fully qualified target forms:
- a:exe:a-exe
Found 1 target matching a:a-exe.
Loading

0 comments on commit f1fbee2

Please sign in to comment.