Skip to content

Commit 3b12960

Browse files
authored
Merge pull request #9744 from cabalism/add/command-target
Add a cabal target command
2 parents 4edd5c4 + f1fbee2 commit 3b12960

28 files changed

+659
-2
lines changed

cabal-install/cabal-install.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -110,6 +110,7 @@ library
110110
Distribution.Client.CmdRepl
111111
Distribution.Client.CmdRun
112112
Distribution.Client.CmdSdist
113+
Distribution.Client.CmdTarget
113114
Distribution.Client.CmdTest
114115
Distribution.Client.CmdUpdate
115116
Distribution.Client.Compat.Directory
Lines changed: 224 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,224 @@
1+
{-# LANGUAGE NamedFieldPuns #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE RecordWildCards #-}
4+
{-# LANGUAGE ScopedTypeVariables #-}
5+
6+
module Distribution.Client.CmdTarget
7+
( targetCommand
8+
, targetAction
9+
) where
10+
11+
import Distribution.Client.Compat.Prelude
12+
import Prelude ()
13+
14+
import qualified Data.Map as Map
15+
import Distribution.Client.CmdBuild (selectComponentTarget, selectPackageTargets)
16+
import Distribution.Client.CmdErrorMessages
17+
import Distribution.Client.InstallPlan
18+
import qualified Distribution.Client.InstallPlan as InstallPlan
19+
import Distribution.Client.NixStyleOptions
20+
( NixStyleFlags (..)
21+
, defaultNixStyleFlags
22+
, nixStyleOptions
23+
)
24+
import Distribution.Client.ProjectOrchestration
25+
import Distribution.Client.ProjectPlanning
26+
import Distribution.Client.Setup
27+
( ConfigFlags (..)
28+
, GlobalFlags
29+
)
30+
import Distribution.Client.TargetProblem
31+
( TargetProblem'
32+
)
33+
import Distribution.Package
34+
import Distribution.Simple.Command
35+
( CommandUI (..)
36+
, usageAlternatives
37+
)
38+
import Distribution.Simple.Flag (fromFlagOrDefault)
39+
import Distribution.Simple.Utils
40+
( noticeDoc
41+
, safeHead
42+
, wrapText
43+
)
44+
import Distribution.Verbosity
45+
( normal
46+
)
47+
import Text.PrettyPrint
48+
import qualified Text.PrettyPrint as Pretty
49+
50+
-------------------------------------------------------------------------------
51+
-- Command
52+
-------------------------------------------------------------------------------
53+
54+
targetCommand :: CommandUI (NixStyleFlags ())
55+
targetCommand =
56+
CommandUI
57+
{ commandName = "v2-target"
58+
, commandSynopsis = "Target a subset of all targets."
59+
, commandUsage = usageAlternatives "v2-target" ["[TARGETS]"]
60+
, commandDescription =
61+
Just . const . render $
62+
vcat
63+
[ intro
64+
, vcat $ punctuate (text "\n") [targetForms, ctypes, Pretty.empty]
65+
, caution
66+
, unique
67+
]
68+
, commandNotes = Just $ \pname -> render $ examples pname
69+
, commandDefaultFlags = defaultNixStyleFlags ()
70+
, commandOptions = nixStyleOptions (const [])
71+
}
72+
where
73+
intro =
74+
text . wrapText $
75+
"Discover targets in a project for use with other commands taking [TARGETS].\n\n"
76+
++ "This command, like many others, takes [TARGETS]. Taken together, these will"
77+
++ " select for a set of targets in the project. When none are supplied, the"
78+
++ " command acts as if 'all' was supplied."
79+
++ " Targets in the returned subset are shown sorted and fully-qualified."
80+
81+
targetForms =
82+
vcat
83+
[ text "A [TARGETS] item can be one of these target forms:"
84+
, nest 1 . vcat $
85+
(char '-' <+>)
86+
<$> [ text "a package target (e.g. [pkg:]package)"
87+
, text "a component target (e.g. [package:][ctype:]component)"
88+
, text "all packages (e.g. all)"
89+
, text "components of a particular type (e.g. package:ctypes or all:ctypes)"
90+
, text "a module target: (e.g. [package:][ctype:]module)"
91+
, text "a filepath target: (e.g. [package:][ctype:]filepath)"
92+
]
93+
]
94+
95+
ctypes =
96+
vcat
97+
[ text "The ctypes, in short form and (long form), can be one of:"
98+
, nest 1 . vcat $
99+
(char '-' <+>)
100+
<$> [ "libs" <+> parens "libraries"
101+
, "exes" <+> parens "executables"
102+
, "tests"
103+
, "benches" <+> parens "benchmarks"
104+
, "flibs" <+> parens "foreign-libraries"
105+
]
106+
]
107+
108+
caution =
109+
text . wrapText $
110+
"WARNING: For a package, all, module or filepath target, cabal target [TARGETS] \
111+
\ will only show 'libs' and 'exes' of the [TARGETS] by default. To also show \
112+
\ tests and benchmarks, enable them with '--enable-tests' and \
113+
\ '--enable-benchmarks'."
114+
115+
unique =
116+
text . wrapText $
117+
"NOTE: For commands expecting a unique TARGET, a fully-qualified target is the safe \
118+
\ way to go but it may be convenient to type out a shorter TARGET. For example, if the \
119+
\ set of 'cabal target all:exes' has one item then 'cabal list-bin all:exes' will \
120+
\ work too."
121+
122+
examples pname =
123+
vcat
124+
[ text "Examples" Pretty.<> colon
125+
, nest 2 $
126+
vcat
127+
[ vcat
128+
[ text pname <+> text "v2-target all"
129+
, nest 2 $ text "Targets of the package in the current directory or all packages in the project"
130+
]
131+
, vcat
132+
[ text pname <+> text "v2-target pkgname"
133+
, nest 2 $ text "Targets of the package named pkgname in the project"
134+
]
135+
, vcat
136+
[ text pname <+> text "v2-target ./pkgfoo"
137+
, nest 2 $ text "Targets of the package in the ./pkgfoo directory"
138+
]
139+
, vcat
140+
[ text pname <+> text "v2-target cname"
141+
, nest 2 $ text "Targets of the component named cname in the project"
142+
]
143+
]
144+
]
145+
146+
-------------------------------------------------------------------------------
147+
-- Action
148+
-------------------------------------------------------------------------------
149+
150+
targetAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO ()
151+
targetAction flags@NixStyleFlags{..} ts globalFlags = do
152+
ProjectBaseContext
153+
{ distDirLayout
154+
, cabalDirLayout
155+
, projectConfig
156+
, localPackages
157+
} <-
158+
establishProjectBaseContext verbosity cliConfig OtherCommand
159+
160+
(_, elaboratedPlan, _, _, _) <-
161+
rebuildInstallPlan
162+
verbosity
163+
distDirLayout
164+
cabalDirLayout
165+
projectConfig
166+
localPackages
167+
Nothing
168+
169+
targetSelectors <-
170+
either (reportTargetSelectorProblems verbosity) return
171+
=<< readTargetSelectors localPackages Nothing targetStrings
172+
173+
targets :: TargetsMap <-
174+
either (reportBuildTargetProblems verbosity) return $
175+
resolveTargets
176+
selectPackageTargets
177+
selectComponentTarget
178+
elaboratedPlan
179+
Nothing
180+
targetSelectors
181+
182+
printTargetForms verbosity targetStrings targets elaboratedPlan
183+
where
184+
verbosity = fromFlagOrDefault normal (configVerbosity configFlags)
185+
targetStrings = if null ts then ["all"] else ts
186+
cliConfig =
187+
commandLineFlagsToProjectConfig
188+
globalFlags
189+
flags
190+
mempty
191+
192+
reportBuildTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
193+
reportBuildTargetProblems verbosity = reportTargetProblems verbosity "target"
194+
195+
printTargetForms :: Verbosity -> [String] -> TargetsMap -> ElaboratedInstallPlan -> IO ()
196+
printTargetForms verbosity targetStrings targets elaboratedPlan =
197+
noticeDoc verbosity $
198+
vcat
199+
[ text "Fully qualified target forms" Pretty.<> colon
200+
, nest 1 $ vcat [text "-" <+> text tf | tf <- targetForms]
201+
, found
202+
]
203+
where
204+
found =
205+
let n = length targets
206+
t = if n == 1 then "target" else "targets"
207+
query = intercalate ", " targetStrings
208+
in text "Found" <+> int n <+> text t <+> text "matching" <+> text query Pretty.<> char '.'
209+
210+
localPkgs =
211+
[x | Configured x@ElaboratedConfiguredPackage{elabLocalToProject = True} <- InstallPlan.toList elaboratedPlan]
212+
213+
targetForm ct x =
214+
let pkgId@PackageIdentifier{pkgName = n} = elabPkgSourceId x
215+
in render $ pretty n Pretty.<> colon Pretty.<> text (showComponentTarget pkgId ct)
216+
217+
targetForms =
218+
sort $
219+
catMaybes
220+
[ targetForm ct <$> pkg
221+
| (u :: UnitId, xs) <- Map.toAscList targets
222+
, let pkg = safeHead $ filter ((== u) . elabUnitId) localPkgs
223+
, (ct :: ComponentTarget, _) <- xs
224+
]

cabal-install/src/Distribution/Client/Main.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -130,6 +130,7 @@ import qualified Distribution.Client.CmdPath as CmdPath
130130
import qualified Distribution.Client.CmdRepl as CmdRepl
131131
import qualified Distribution.Client.CmdRun as CmdRun
132132
import qualified Distribution.Client.CmdSdist as CmdSdist
133+
import qualified Distribution.Client.CmdTarget as CmdTarget
133134
import qualified Distribution.Client.CmdTest as CmdTest
134135
import qualified Distribution.Client.CmdUpdate as CmdUpdate
135136

@@ -460,6 +461,7 @@ mainWorker args = do
460461
, newCmd CmdExec.execCommand CmdExec.execAction
461462
, newCmd CmdClean.cleanCommand CmdClean.cleanAction
462463
, newCmd CmdSdist.sdistCommand CmdSdist.sdistAction
464+
, newCmd CmdTarget.targetCommand CmdTarget.targetAction
463465
, legacyCmd configureExCommand configureAction
464466
, legacyCmd buildCommand buildAction
465467
, legacyCmd replCommand replAction

cabal-install/src/Distribution/Client/ProjectOrchestration.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -934,7 +934,6 @@ distinctTargetComponents targetsMap =
934934

935935
------------------------------------------------------------------------------
936936
-- Displaying what we plan to do
937-
--
938937

939938
-- | Print a user-oriented presentation of the install plan, indicating what
940939
-- will be built.

cabal-install/src/Distribution/Client/Setup.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -282,6 +282,7 @@ globalCommand commands =
282282
, "unpack"
283283
, "init"
284284
, "configure"
285+
, "target"
285286
, "build"
286287
, "clean"
287288
, "run"
@@ -302,6 +303,7 @@ globalCommand commands =
302303
, "path"
303304
, "new-build"
304305
, "new-configure"
306+
, "new-target"
305307
, "new-repl"
306308
, "new-freeze"
307309
, "new-run"
@@ -334,7 +336,8 @@ globalCommand commands =
334336
, "v1-register"
335337
, "v1-reconfigure"
336338
, -- v2 commands, nix-style
337-
"v2-build"
339+
"v2-target"
340+
, "v2-build"
338341
, "v2-configure"
339342
, "v2-repl"
340343
, "v2-freeze"
@@ -379,6 +382,7 @@ globalCommand commands =
379382
, addCmd "gen-bounds"
380383
, addCmd "outdated"
381384
, addCmd "path"
385+
, addCmd "target"
382386
, par
383387
, startGroup "project building and installing"
384388
, addCmd "build"
@@ -406,6 +410,7 @@ globalCommand commands =
406410
, addCmd "hscolour"
407411
, par
408412
, startGroup "new-style projects (forwards-compatible aliases)"
413+
, addCmd "v2-target"
409414
, addCmd "v2-build"
410415
, addCmd "v2-configure"
411416
, addCmd "v2-repl"
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
# cabal v2-target
2+
Configuration is affected by the following files:
3+
- cabal.project
4+
Resolving dependencies...
5+
Fully qualified target forms:
6+
- a:bench:a-bench
7+
- b:bench:b-bench
8+
Found 2 targets matching all:benches.
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
# cabal v2-target
2+
Configuration is affected by the following files:
3+
- cabal.project
4+
Resolving dependencies...
5+
Fully qualified target forms:
6+
- a:bench:a-bench
7+
- a:exe:a-exe
8+
- a:lib:a
9+
- a:lib:a-sublib
10+
- b:bench:b-bench
11+
- b:exe:b-exe
12+
- b:lib:b
13+
- b:lib:b-sublib
14+
- c:lib:c
15+
Found 9 targets matching all.
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
# cabal v2-target
2+
Configuration is affected by the following files:
3+
- cabal.project
4+
Resolving dependencies...
5+
Fully qualified target forms:
6+
- a:exe:a-exe
7+
- a:lib:a
8+
- a:lib:a-sublib
9+
- a:test:a-test
10+
- b:exe:b-exe
11+
- b:lib:b
12+
- b:lib:b-sublib
13+
- b:test:b-test
14+
- c:lib:c
15+
Found 9 targets matching all.
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
# cabal v2-target
2+
Configuration is affected by the following files:
3+
- cabal.project
4+
Resolving dependencies...
5+
Fully qualified target forms:
6+
- a:exe:a-exe
7+
- b:exe:b-exe
8+
Found 2 targets matching all:exes.
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
# cabal v2-target
2+
Configuration is affected by the following files:
3+
- cabal.project
4+
Resolving dependencies...
5+
Fully qualified target forms:
6+
- a:test:a-test
7+
- b:test:b-test
8+
Found 2 targets matching all:tests.
Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
# cabal v2-target
2+
Configuration is affected by the following files:
3+
- cabal.project
4+
Resolving dependencies...
5+
Fully qualified target forms:
6+
- a:bench:a-bench
7+
Found 1 target matching a:bench:a-bench.
8+
# cabal v2-target
9+
Configuration is affected by the following files:
10+
- cabal.project
11+
Fully qualified target forms:
12+
- a:bench:a-bench
13+
Found 1 target matching bench:a-bench.
14+
# cabal v2-target
15+
Configuration is affected by the following files:
16+
- cabal.project
17+
Fully qualified target forms:
18+
- a:bench:a-bench
19+
Found 1 target matching a:a-bench.
Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
# cabal v2-target
2+
Configuration is affected by the following files:
3+
- cabal.project
4+
Resolving dependencies...
5+
Fully qualified target forms:
6+
- a:exe:a-exe
7+
Found 1 target matching a:exe:a-exe.
8+
# cabal v2-target
9+
Configuration is affected by the following files:
10+
- cabal.project
11+
Fully qualified target forms:
12+
- a:exe:a-exe
13+
Found 1 target matching exe:a-exe.
14+
# cabal v2-target
15+
Configuration is affected by the following files:
16+
- cabal.project
17+
Fully qualified target forms:
18+
- a:exe:a-exe
19+
Found 1 target matching a:a-exe.

0 commit comments

Comments
 (0)