Skip to content

Commit 1a6eb9b

Browse files
committed
Drop sub-component targets
1 parent 39d42e6 commit 1a6eb9b

22 files changed

+153
-1347
lines changed

Cabal/src/Distribution/Simple/BuildTarget.hs

Lines changed: 28 additions & 344 deletions
Large diffs are not rendered by default.

cabal-install/cabal-install.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -303,7 +303,6 @@ test-suite unit-tests
303303
UnitTests.Distribution.Client.InstallPlan
304304
UnitTests.Distribution.Client.JobControl
305305
UnitTests.Distribution.Client.ProjectConfig
306-
UnitTests.Distribution.Client.ProjectPlanning
307306
UnitTests.Distribution.Client.Store
308307
UnitTests.Distribution.Client.Tar
309308
UnitTests.Distribution.Client.Targets

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

Lines changed: 4 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ module Distribution.Client.CmdBench
88

99
-- * Internals exposed for testing
1010
, componentNotBenchmarkProblem
11-
, isSubComponentProblem
1211
, noBenchmarksProblem
1312
, selectPackageTargets
1413
, selectComponentTarget
@@ -197,25 +196,17 @@ selectPackageTargets targetSelector targets
197196
-- For the @bench@ command we just need to check it is a benchmark, in addition
198197
-- to the basic checks on being buildable etc.
199198
selectComponentTarget
200-
:: SubComponentTarget
201-
-> AvailableTarget k
199+
:: AvailableTarget k
202200
-> Either BenchTargetProblem k
203-
selectComponentTarget subtarget@WholeComponent t
201+
selectComponentTarget t
204202
| CBenchName _ <- availableTargetComponentName t =
205-
selectComponentTargetBasic subtarget t
203+
selectComponentTargetBasic t
206204
| otherwise =
207205
Left
208206
( componentNotBenchmarkProblem
209207
(availableTargetPackageId t)
210208
(availableTargetComponentName t)
211209
)
212-
selectComponentTarget subtarget t =
213-
Left
214-
( isSubComponentProblem
215-
(availableTargetPackageId t)
216-
(availableTargetComponentName t)
217-
subtarget
218-
)
219210

220211
-- | The various error conditions that can occur when matching a
221212
-- 'TargetSelector' against 'AvailableTarget's for the @bench@ command.
@@ -224,8 +215,6 @@ data BenchProblem
224215
TargetProblemNoBenchmarks TargetSelector
225216
| -- | The 'TargetSelector' refers to a component that is not a benchmark
226217
TargetProblemComponentNotBenchmark PackageId ComponentName
227-
| -- | Asking to benchmark an individual file or module is not supported
228-
TargetProblemIsSubComponent PackageId ComponentName SubComponentTarget
229218
deriving (Eq, Show)
230219

231220
type BenchTargetProblem = TargetProblem BenchProblem
@@ -238,15 +227,6 @@ componentNotBenchmarkProblem pkgid name =
238227
CustomTargetProblem $
239228
TargetProblemComponentNotBenchmark pkgid name
240229

241-
isSubComponentProblem
242-
:: PackageId
243-
-> ComponentName
244-
-> SubComponentTarget
245-
-> TargetProblem BenchProblem
246-
isSubComponentProblem pkgid name subcomponent =
247-
CustomTargetProblem $
248-
TargetProblemIsSubComponent pkgid name subcomponent
249-
250230
reportTargetProblems :: Verbosity -> [BenchTargetProblem] -> IO a
251231
reportTargetProblems verbosity =
252232
dieWithException verbosity . RenderBenchTargetProblem . map renderBenchTargetProblem
@@ -283,13 +263,4 @@ renderBenchProblem (TargetProblemComponentNotBenchmark pkgid cname) =
283263
++ prettyShow pkgid
284264
++ "."
285265
where
286-
targetSelector = TargetComponent pkgid cname WholeComponent
287-
renderBenchProblem (TargetProblemIsSubComponent pkgid cname subtarget) =
288-
"The bench command can only run benchmarks as a whole, "
289-
++ "not files or modules within them, but the target '"
290-
++ showTargetSelector targetSelector
291-
++ "' refers to "
292-
++ renderTargetSelector targetSelector
293-
++ "."
294-
where
295-
targetSelector = TargetComponent pkgid cname subtarget
266+
targetSelector = TargetComponent pkgid cname

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

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -226,8 +226,7 @@ selectPackageTargets targetSelector targets
226226
--
227227
-- For the @build@ command we just need the basic checks on being buildable etc.
228228
selectComponentTarget
229-
:: SubComponentTarget
230-
-> AvailableTarget k
229+
:: AvailableTarget k
231230
-> Either TargetProblem' k
232231
selectComponentTarget = selectComponentTargetBasic
233232

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

Lines changed: 10 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,6 @@ import Distribution.Client.TargetProblem
2424
import Distribution.Client.TargetSelector
2525
( ComponentKind (..)
2626
, ComponentKindFilter
27-
, SubComponentTarget (..)
2827
, TargetSelector (..)
2928
, componentKind
3029
, showTargetSelector
@@ -142,28 +141,18 @@ renderTargetSelector (TargetAllPackages (Just kfilter)) =
142141
"all the "
143142
++ renderComponentKind Plural kfilter
144143
++ " in the project"
145-
renderTargetSelector (TargetComponent pkgid cname subtarget) =
146-
renderSubComponentTarget subtarget
147-
++ "the "
144+
renderTargetSelector (TargetComponent pkgid cname) =
145+
"the "
148146
++ renderComponentName (packageName pkgid) cname
149-
renderTargetSelector (TargetComponentUnknown pkgname (Left ucname) subtarget) =
150-
renderSubComponentTarget subtarget
151-
++ "the component "
147+
renderTargetSelector (TargetComponentUnknown pkgname (Left ucname)) =
148+
"the component "
152149
++ prettyShow ucname
153150
++ " in the package "
154151
++ prettyShow pkgname
155-
renderTargetSelector (TargetComponentUnknown pkgname (Right cname) subtarget) =
156-
renderSubComponentTarget subtarget
157-
++ "the "
152+
renderTargetSelector (TargetComponentUnknown pkgname (Right cname)) =
153+
"the "
158154
++ renderComponentName pkgname cname
159155

160-
renderSubComponentTarget :: SubComponentTarget -> String
161-
renderSubComponentTarget WholeComponent = ""
162-
renderSubComponentTarget (FileTarget filename) =
163-
"the file " ++ filename ++ " in "
164-
renderSubComponentTarget (ModuleTarget modname) =
165-
"the module " ++ prettyShow modname ++ " in "
166-
167156
renderOptionalStanza :: Plural -> OptionalStanza -> String
168157
renderOptionalStanza Singular TestStanzas = "test suite"
169158
renderOptionalStanza Plural TestStanzas = "test suites"
@@ -260,7 +249,7 @@ renderTargetProblem verb _ (TargetAvailableInIndex pkgname) =
260249
++ "in this project (either directly or indirectly), but it is in the current "
261250
++ "package index. If you want to add it to the project then edit the "
262251
++ "cabal.project file."
263-
renderTargetProblem verb _ (TargetComponentNotProjectLocal pkgid cname _) =
252+
renderTargetProblem verb _ (TargetComponentNotProjectLocal pkgid cname) =
264253
"Cannot "
265254
++ verb
266255
++ " the "
@@ -273,7 +262,7 @@ renderTargetProblem verb _ (TargetComponentNotProjectLocal pkgid cname _) =
273262
++ "non-local dependencies. To run test suites or benchmarks from "
274263
++ "dependencies you can unpack the package locally and adjust the "
275264
++ "cabal.project file to include that package directory."
276-
renderTargetProblem verb _ (TargetComponentNotBuildable pkgid cname _) =
265+
renderTargetProblem verb _ (TargetComponentNotBuildable pkgid cname) =
277266
"Cannot "
278267
++ verb
279268
++ " the "
@@ -286,7 +275,7 @@ renderTargetProblem verb _ (TargetComponentNotBuildable pkgid cname _) =
286275
++ "property is conditional on flags. Alternatively you may simply have to "
287276
++ "edit the .cabal file to declare it as buildable and fix any resulting "
288277
++ "build problems."
289-
renderTargetProblem verb _ (TargetOptionalStanzaDisabledByUser _ cname _) =
278+
renderTargetProblem verb _ (TargetOptionalStanzaDisabledByUser _ cname) =
290279
"Cannot "
291280
++ verb
292281
++ " the "
@@ -305,7 +294,7 @@ renderTargetProblem verb _ (TargetOptionalStanzaDisabledByUser _ cname _) =
305294
++ "explanation."
306295
where
307296
compkinds = renderComponentKind Plural (componentKind cname)
308-
renderTargetProblem verb _ (TargetOptionalStanzaDisabledBySolver pkgid cname _) =
297+
renderTargetProblem verb _ (TargetOptionalStanzaDisabledBySolver pkgid cname) =
309298
"Cannot "
310299
++ verb
311300
++ " the "

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

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -268,8 +268,7 @@ selectPackageTargets haddockFlags targetSelector targets
268268
-- For the @haddock@ command we just need the basic checks on being buildable
269269
-- etc.
270270
selectComponentTarget
271-
:: SubComponentTarget
272-
-> AvailableTarget k
271+
:: AvailableTarget k
273272
-> Either TargetProblem' k
274273
selectComponentTarget = selectComponentTargetBasic
275274

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

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -733,7 +733,7 @@ partitionToKnownTargetsAndHackagePackages verbosity pkgDb elaboratedPlan targetS
733733

734734
let
735735
targetSelectors' = flip filter targetSelectors $ \case
736-
TargetComponentUnknown name _ _
736+
TargetComponentUnknown name _
737737
| name `elem` hackageNames -> False
738738
TargetPackageNamed name _
739739
| name `elem` hackageNames -> False
@@ -944,7 +944,7 @@ warnIfNoExes verbosity buildCtx =
944944
selectors = concatMap (NE.toList . snd) targets
945945
noExes = null $ catMaybes $ exeMaybe <$> components
946946

947-
exeMaybe (ComponentTarget (CExeName exe) _) = Just exe
947+
exeMaybe (ComponentTarget (CExeName exe)) = Just exe
948948
exeMaybe _ = Nothing
949949

950950
-- | Return the package specifiers and non-global environment file entries.
@@ -1020,7 +1020,7 @@ installUnitExes
10201020
traverse_ installAndWarn exes
10211021
where
10221022
exes = catMaybes $ (exeMaybe . fst) <$> components
1023-
exeMaybe (ComponentTarget (CExeName exe) _) = Just exe
1023+
exeMaybe (ComponentTarget (CExeName exe)) = Just exe
10241024
exeMaybe _ = Nothing
10251025
installAndWarn exe = do
10261026
success <-
@@ -1116,7 +1116,7 @@ entriesForLibraryComponents :: TargetsMap -> [GhcEnvironmentFileEntry]
11161116
entriesForLibraryComponents = Map.foldrWithKey' (\k v -> mappend (go k v)) []
11171117
where
11181118
hasLib :: (ComponentTarget, NonEmpty TargetSelector) -> Bool
1119-
hasLib (ComponentTarget (CLibName _) _, _) = True
1119+
hasLib (ComponentTarget (CLibName _), _) = True
11201120
hasLib _ = False
11211121

11221122
go
@@ -1242,8 +1242,7 @@ selectPackageTargets targetSelector targets
12421242
--
12431243
-- For the @build@ command we just need the basic checks on being buildable etc.
12441244
selectComponentTarget
1245-
:: SubComponentTarget
1246-
-> AvailableTarget k
1245+
:: AvailableTarget k
12471246
-> Either TargetProblem' k
12481247
selectComponentTarget = selectComponentTargetBasic
12491248

cabal-install/src/Distribution/Client/CmdInstall/ClientInstallTargetSelector.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ woPackageTargets :: WithoutProjectTargetSelector -> TargetSelector
5252
woPackageTargets (WoPackageId pid) =
5353
TargetPackageNamed (pkgName pid) Nothing
5454
woPackageTargets (WoPackageComponent pid cn) =
55-
TargetComponentUnknown (pkgName pid) (Right cn) WholeComponent
55+
TargetComponentUnknown (pkgName pid) (Right cn)
5656
woPackageTargets (WoURI _) =
5757
TargetAllPackages (Just ExeKind)
5858

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

Lines changed: 4 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -290,10 +290,9 @@ selectPackageTargets targetSelector targets
290290
-- (an executable, a test, or a benchmark), in addition
291291
-- to the basic checks on being buildable etc.
292292
selectComponentTarget
293-
:: SubComponentTarget
294-
-> AvailableTarget k
293+
:: AvailableTarget k
295294
-> Either ListBinTargetProblem k
296-
selectComponentTarget subtarget@WholeComponent t =
295+
selectComponentTarget t =
297296
case availableTargetComponentName t of
298297
CExeName _ -> component
299298
CTestName _ -> component
@@ -303,14 +302,7 @@ selectComponentTarget subtarget@WholeComponent t =
303302
where
304303
pkgid = availableTargetPackageId t
305304
cname = availableTargetComponentName t
306-
component = selectComponentTargetBasic subtarget t
307-
selectComponentTarget subtarget t =
308-
Left
309-
( isSubComponentProblem
310-
(availableTargetPackageId t)
311-
(availableTargetComponentName t)
312-
subtarget
313-
)
305+
component = selectComponentTargetBasic t
314306

315307
-- | The various error conditions that can occur when matching a
316308
-- 'TargetSelector' against 'AvailableTarget's for the @run@ command.
@@ -323,8 +315,6 @@ data ListBinProblem
323315
TargetProblemMultipleTargets TargetsMap
324316
| -- | The 'TargetSelector' refers to a component that is not an executable
325317
TargetProblemComponentNotRightKind PackageId ComponentName
326-
| -- | Asking to run an individual file or module is not supported
327-
TargetProblemIsSubComponent PackageId ComponentName SubComponentTarget
328318
deriving (Eq, Show)
329319

330320
type ListBinTargetProblem = TargetProblem ListBinProblem
@@ -345,15 +335,6 @@ componentNotRightKindProblem pkgid name =
345335
CustomTargetProblem $
346336
TargetProblemComponentNotRightKind pkgid name
347337

348-
isSubComponentProblem
349-
:: PackageId
350-
-> ComponentName
351-
-> SubComponentTarget
352-
-> TargetProblem ListBinProblem
353-
isSubComponentProblem pkgid name subcomponent =
354-
CustomTargetProblem $
355-
TargetProblemIsSubComponent pkgid name subcomponent
356-
357338
reportTargetProblems :: Verbosity -> [ListBinTargetProblem] -> IO a
358339
reportTargetProblems verbosity =
359340
dieWithException verbosity . ListBinTargetException . unlines . map renderListBinTargetProblem
@@ -404,16 +385,7 @@ renderListBinProblem (TargetProblemComponentNotRightKind pkgid cname) =
404385
++ prettyShow pkgid
405386
++ "."
406387
where
407-
targetSelector = TargetComponent pkgid cname WholeComponent
408-
renderListBinProblem (TargetProblemIsSubComponent pkgid cname subtarget) =
409-
"The list-bin command can only find a binary as a whole, "
410-
++ "not files or modules within them, but the target '"
411-
++ showTargetSelector targetSelector
412-
++ "' refers to "
413-
++ renderTargetSelector targetSelector
414-
++ "."
415-
where
416-
targetSelector = TargetComponent pkgid cname subtarget
388+
targetSelector = TargetComponent pkgid cname
417389
renderListBinProblem (TargetProblemNoRightComps targetSelector) =
418390
"Cannot list-bin the target '"
419391
++ showTargetSelector targetSelector

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

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -715,8 +715,7 @@ selectPackageTargetsSingle decision targetSelector targets
715715
--
716716
-- For the @repl@ command we just need the basic checks on being buildable etc.
717717
selectComponentTarget
718-
:: SubComponentTarget
719-
-> AvailableTarget k
718+
:: AvailableTarget k
720719
-> Either ReplTargetProblem k
721720
selectComponentTarget = selectComponentTargetBasic
722721

0 commit comments

Comments
 (0)