Skip to content

Commit

Permalink
Drop sub-component targets (haskell#8966)
Browse files Browse the repository at this point in the history
This change removes support for building sub-component targets in
cabal-install, since no versions of Cabal support this feature.

The test RunMainBad is also dropped because without the concept of a
file target, RunMainBad is the same test as ScriptBad.
  • Loading branch information
andreabedini committed Jan 29, 2024
1 parent e7abea5 commit 3f4c81f
Show file tree
Hide file tree
Showing 29 changed files with 183 additions and 1,409 deletions.
400 changes: 36 additions & 364 deletions Cabal/src/Distribution/Simple/BuildTarget.hs

Large diffs are not rendered by default.

1 change: 0 additions & 1 deletion cabal-install/cabal-install.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -310,7 +310,6 @@ test-suite unit-tests
UnitTests.Distribution.Client.InstallPlan
UnitTests.Distribution.Client.JobControl
UnitTests.Distribution.Client.ProjectConfig
UnitTests.Distribution.Client.ProjectPlanning
UnitTests.Distribution.Client.Store
UnitTests.Distribution.Client.Tar
UnitTests.Distribution.Client.Targets
Expand Down
37 changes: 4 additions & 33 deletions cabal-install/src/Distribution/Client/CmdBench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ module Distribution.Client.CmdBench

-- * Internals exposed for testing
, componentNotBenchmarkProblem
, isSubComponentProblem
, noBenchmarksProblem
, selectPackageTargets
, selectComponentTarget
Expand Down Expand Up @@ -197,25 +196,17 @@ selectPackageTargets targetSelector targets
-- For the @bench@ command we just need to check it is a benchmark, in addition
-- to the basic checks on being buildable etc.
selectComponentTarget
:: SubComponentTarget
-> AvailableTarget k
:: AvailableTarget k
-> Either BenchTargetProblem k
selectComponentTarget subtarget@WholeComponent t
selectComponentTarget t
| CBenchName _ <- availableTargetComponentName t =
selectComponentTargetBasic subtarget t
selectComponentTargetBasic t
| otherwise =
Left
( componentNotBenchmarkProblem
(availableTargetPackageId t)
(availableTargetComponentName t)
)
selectComponentTarget subtarget t =
Left
( isSubComponentProblem
(availableTargetPackageId t)
(availableTargetComponentName t)
subtarget
)

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

type BenchTargetProblem = TargetProblem BenchProblem
Expand All @@ -238,15 +227,6 @@ componentNotBenchmarkProblem pkgid name =
CustomTargetProblem $
TargetProblemComponentNotBenchmark pkgid name

isSubComponentProblem
:: PackageId
-> ComponentName
-> SubComponentTarget
-> TargetProblem BenchProblem
isSubComponentProblem pkgid name subcomponent =
CustomTargetProblem $
TargetProblemIsSubComponent pkgid name subcomponent

reportTargetProblems :: Verbosity -> [BenchTargetProblem] -> IO a
reportTargetProblems verbosity =
dieWithException verbosity . RenderBenchTargetProblem . map renderBenchTargetProblem
Expand Down Expand Up @@ -283,13 +263,4 @@ renderBenchProblem (TargetProblemComponentNotBenchmark pkgid cname) =
++ prettyShow pkgid
++ "."
where
targetSelector = TargetComponent pkgid cname WholeComponent
renderBenchProblem (TargetProblemIsSubComponent pkgid cname subtarget) =
"The bench command can only run benchmarks as a whole, "
++ "not files or modules within them, but the target '"
++ showTargetSelector targetSelector
++ "' refers to "
++ renderTargetSelector targetSelector
++ "."
where
targetSelector = TargetComponent pkgid cname subtarget
targetSelector = TargetComponent pkgid cname
3 changes: 1 addition & 2 deletions cabal-install/src/Distribution/Client/CmdBuild.hs
Original file line number Diff line number Diff line change
Expand Up @@ -226,8 +226,7 @@ selectPackageTargets targetSelector targets
--
-- For the @build@ command we just need the basic checks on being buildable etc.
selectComponentTarget
:: SubComponentTarget
-> AvailableTarget k
:: AvailableTarget k
-> Either TargetProblem' k
selectComponentTarget = selectComponentTargetBasic

Expand Down
31 changes: 10 additions & 21 deletions cabal-install/src/Distribution/Client/CmdErrorMessages.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ import Distribution.Client.TargetProblem
import Distribution.Client.TargetSelector
( ComponentKind (..)
, ComponentKindFilter
, SubComponentTarget (..)
, TargetSelector (..)
, componentKind
, showTargetSelector
Expand Down Expand Up @@ -142,28 +141,18 @@ renderTargetSelector (TargetAllPackages (Just kfilter)) =
"all the "
++ renderComponentKind Plural kfilter
++ " in the project"
renderTargetSelector (TargetComponent pkgid cname subtarget) =
renderSubComponentTarget subtarget
++ "the "
renderTargetSelector (TargetComponent pkgid cname) =
"the "
++ renderComponentName (packageName pkgid) cname
renderTargetSelector (TargetComponentUnknown pkgname (Left ucname) subtarget) =
renderSubComponentTarget subtarget
++ "the component "
renderTargetSelector (TargetComponentUnknown pkgname (Left ucname)) =
"the component "
++ prettyShow ucname
++ " in the package "
++ prettyShow pkgname
renderTargetSelector (TargetComponentUnknown pkgname (Right cname) subtarget) =
renderSubComponentTarget subtarget
++ "the "
renderTargetSelector (TargetComponentUnknown pkgname (Right cname)) =
"the "
++ renderComponentName pkgname cname

renderSubComponentTarget :: SubComponentTarget -> String
renderSubComponentTarget WholeComponent = ""
renderSubComponentTarget (FileTarget filename) =
"the file " ++ filename ++ " in "
renderSubComponentTarget (ModuleTarget modname) =
"the module " ++ prettyShow modname ++ " in "

renderOptionalStanza :: Plural -> OptionalStanza -> String
renderOptionalStanza Singular TestStanzas = "test suite"
renderOptionalStanza Plural TestStanzas = "test suites"
Expand Down Expand Up @@ -260,7 +249,7 @@ renderTargetProblem verb _ (TargetAvailableInIndex pkgname) =
++ "in this project (either directly or indirectly), but it is in the current "
++ "package index. If you want to add it to the project then edit the "
++ "cabal.project file."
renderTargetProblem verb _ (TargetComponentNotProjectLocal pkgid cname _) =
renderTargetProblem verb _ (TargetComponentNotProjectLocal pkgid cname) =
"Cannot "
++ verb
++ " the "
Expand All @@ -273,7 +262,7 @@ renderTargetProblem verb _ (TargetComponentNotProjectLocal pkgid cname _) =
++ "non-local dependencies. To run test suites or benchmarks from "
++ "dependencies you can unpack the package locally and adjust the "
++ "cabal.project file to include that package directory."
renderTargetProblem verb _ (TargetComponentNotBuildable pkgid cname _) =
renderTargetProblem verb _ (TargetComponentNotBuildable pkgid cname) =
"Cannot "
++ verb
++ " the "
Expand All @@ -286,7 +275,7 @@ renderTargetProblem verb _ (TargetComponentNotBuildable pkgid cname _) =
++ "property is conditional on flags. Alternatively you may simply have to "
++ "edit the .cabal file to declare it as buildable and fix any resulting "
++ "build problems."
renderTargetProblem verb _ (TargetOptionalStanzaDisabledByUser _ cname _) =
renderTargetProblem verb _ (TargetOptionalStanzaDisabledByUser _ cname) =
"Cannot "
++ verb
++ " the "
Expand All @@ -305,7 +294,7 @@ renderTargetProblem verb _ (TargetOptionalStanzaDisabledByUser _ cname _) =
++ "explanation."
where
compkinds = renderComponentKind Plural (componentKind cname)
renderTargetProblem verb _ (TargetOptionalStanzaDisabledBySolver pkgid cname _) =
renderTargetProblem verb _ (TargetOptionalStanzaDisabledBySolver pkgid cname) =
"Cannot "
++ verb
++ " the "
Expand Down
3 changes: 1 addition & 2 deletions cabal-install/src/Distribution/Client/CmdHaddock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -268,8 +268,7 @@ selectPackageTargets haddockFlags targetSelector targets
-- For the @haddock@ command we just need the basic checks on being buildable
-- etc.
selectComponentTarget
:: SubComponentTarget
-> AvailableTarget k
:: AvailableTarget k
-> Either TargetProblem' k
selectComponentTarget = selectComponentTargetBasic

Expand Down
11 changes: 5 additions & 6 deletions cabal-install/src/Distribution/Client/CmdInstall.hs
Original file line number Diff line number Diff line change
Expand Up @@ -774,7 +774,7 @@ partitionToKnownTargetsAndHackagePackages verbosity pkgDb elaboratedPlan targetS

let
targetSelectors' = flip filter targetSelectors $ \case
TargetComponentUnknown name _ _
TargetComponentUnknown name _
| name `elem` hackageNames -> False
TargetPackageNamed name _
| name `elem` hackageNames -> False
Expand Down Expand Up @@ -954,7 +954,7 @@ warnIfNoExes verbosity buildCtx =
selectors = concatMap (NE.toList . snd) targets
noExes = null $ catMaybes $ exeMaybe <$> components

exeMaybe (ComponentTarget (CExeName exe) _) = Just exe
exeMaybe (ComponentTarget (CExeName exe)) = Just exe
exeMaybe _ = Nothing

-- | Return the package specifiers and non-global environment file entries.
Expand Down Expand Up @@ -1034,7 +1034,7 @@ installCheckUnitExes
else traverse_ warnAbout (zip symlinkables exes)
where
exes = catMaybes $ (exeMaybe . fst) <$> components
exeMaybe (ComponentTarget (CExeName exe) _) = Just exe
exeMaybe (ComponentTarget (CExeName exe)) = Just exe
exeMaybe _ = Nothing

warnAbout (True, _) = return ()
Expand Down Expand Up @@ -1136,7 +1136,7 @@ entriesForLibraryComponents :: TargetsMap -> [GhcEnvironmentFileEntry]
entriesForLibraryComponents = Map.foldrWithKey' (\k v -> mappend (go k v)) []
where
hasLib :: (ComponentTarget, NonEmpty TargetSelector) -> Bool
hasLib (ComponentTarget (CLibName _) _, _) = True
hasLib (ComponentTarget (CLibName _), _) = True
hasLib _ = False

go
Expand Down Expand Up @@ -1262,8 +1262,7 @@ selectPackageTargets targetSelector targets
--
-- For the @build@ command we just need the basic checks on being buildable etc.
selectComponentTarget
:: SubComponentTarget
-> AvailableTarget k
:: AvailableTarget k
-> Either TargetProblem' k
selectComponentTarget = selectComponentTargetBasic

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ woPackageTargets :: WithoutProjectTargetSelector -> TargetSelector
woPackageTargets (WoPackageId pid) =
TargetPackageNamed (pkgName pid) Nothing
woPackageTargets (WoPackageComponent pid cn) =
TargetComponentUnknown (pkgName pid) (Right cn) WholeComponent
TargetComponentUnknown (pkgName pid) (Right cn)
woPackageTargets (WoURI _) =
TargetAllPackages (Just ExeKind)

Expand Down
36 changes: 4 additions & 32 deletions cabal-install/src/Distribution/Client/CmdListBin.hs
Original file line number Diff line number Diff line change
Expand Up @@ -290,10 +290,9 @@ selectPackageTargets targetSelector targets
-- (an executable, a test, or a benchmark), in addition
-- to the basic checks on being buildable etc.
selectComponentTarget
:: SubComponentTarget
-> AvailableTarget k
:: AvailableTarget k
-> Either ListBinTargetProblem k
selectComponentTarget subtarget@WholeComponent t =
selectComponentTarget t =
case availableTargetComponentName t of
CExeName _ -> component
CTestName _ -> component
Expand All @@ -303,14 +302,7 @@ selectComponentTarget subtarget@WholeComponent t =
where
pkgid = availableTargetPackageId t
cname = availableTargetComponentName t
component = selectComponentTargetBasic subtarget t
selectComponentTarget subtarget t =
Left
( isSubComponentProblem
(availableTargetPackageId t)
(availableTargetComponentName t)
subtarget
)
component = selectComponentTargetBasic t

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

type ListBinTargetProblem = TargetProblem ListBinProblem
Expand All @@ -345,15 +335,6 @@ componentNotRightKindProblem pkgid name =
CustomTargetProblem $
TargetProblemComponentNotRightKind pkgid name

isSubComponentProblem
:: PackageId
-> ComponentName
-> SubComponentTarget
-> TargetProblem ListBinProblem
isSubComponentProblem pkgid name subcomponent =
CustomTargetProblem $
TargetProblemIsSubComponent pkgid name subcomponent

reportTargetProblems :: Verbosity -> [ListBinTargetProblem] -> IO a
reportTargetProblems verbosity =
dieWithException verbosity . ListBinTargetException . unlines . map renderListBinTargetProblem
Expand Down Expand Up @@ -404,16 +385,7 @@ renderListBinProblem (TargetProblemComponentNotRightKind pkgid cname) =
++ prettyShow pkgid
++ "."
where
targetSelector = TargetComponent pkgid cname WholeComponent
renderListBinProblem (TargetProblemIsSubComponent pkgid cname subtarget) =
"The list-bin command can only find a binary as a whole, "
++ "not files or modules within them, but the target '"
++ showTargetSelector targetSelector
++ "' refers to "
++ renderTargetSelector targetSelector
++ "."
where
targetSelector = TargetComponent pkgid cname subtarget
targetSelector = TargetComponent pkgid cname
renderListBinProblem (TargetProblemNoRightComps targetSelector) =
"Cannot list-bin the target '"
++ showTargetSelector targetSelector
Expand Down
3 changes: 1 addition & 2 deletions cabal-install/src/Distribution/Client/CmdRepl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -734,8 +734,7 @@ selectPackageTargetsSingle decision targetSelector targets
--
-- For the @repl@ command we just need the basic checks on being buildable etc.
selectComponentTarget
:: SubComponentTarget
-> AvailableTarget k
:: AvailableTarget k
-> Either ReplTargetProblem k
selectComponentTarget = selectComponentTargetBasic

Expand Down
36 changes: 4 additions & 32 deletions cabal-install/src/Distribution/Client/CmdRun.hs
Original file line number Diff line number Diff line change
Expand Up @@ -439,10 +439,9 @@ selectPackageTargets targetSelector targets
-- (an executable, a test, or a benchmark), in addition
-- to the basic checks on being buildable etc.
selectComponentTarget
:: SubComponentTarget
-> AvailableTarget k
:: AvailableTarget k
-> Either RunTargetProblem k
selectComponentTarget subtarget@WholeComponent t =
selectComponentTarget t =
case availableTargetComponentName t of
CExeName _ -> component
CTestName _ -> component
Expand All @@ -451,14 +450,7 @@ selectComponentTarget subtarget@WholeComponent t =
where
pkgid = availableTargetPackageId t
cname = availableTargetComponentName t
component = selectComponentTargetBasic subtarget t
selectComponentTarget subtarget t =
Left
( isSubComponentProblem
(availableTargetPackageId t)
(availableTargetComponentName t)
subtarget
)
component = selectComponentTargetBasic t

-- | The various error conditions that can occur when matching a
-- 'TargetSelector' against 'AvailableTarget's for the @run@ command.
Expand All @@ -471,8 +463,6 @@ data RunProblem
TargetProblemMultipleTargets TargetsMap
| -- | The 'TargetSelector' refers to a component that is not an executable
TargetProblemComponentNotExe PackageId ComponentName
| -- | Asking to run an individual file or module is not supported
TargetProblemIsSubComponent PackageId ComponentName SubComponentTarget
deriving (Eq, Show)

type RunTargetProblem = TargetProblem RunProblem
Expand All @@ -493,15 +483,6 @@ componentNotExeProblem pkgid name =
CustomTargetProblem $
TargetProblemComponentNotExe pkgid name

isSubComponentProblem
:: PackageId
-> ComponentName
-> SubComponentTarget
-> TargetProblem RunProblem
isSubComponentProblem pkgid name subcomponent =
CustomTargetProblem $
TargetProblemIsSubComponent pkgid name subcomponent

reportTargetProblems :: Verbosity -> [RunTargetProblem] -> IO a
reportTargetProblems verbosity =
dieWithException verbosity . CmdRunReportTargetProblems . unlines . map renderRunTargetProblem
Expand Down Expand Up @@ -555,16 +536,7 @@ renderRunProblem (TargetProblemComponentNotExe pkgid cname) =
++ prettyShow pkgid
++ "."
where
targetSelector = TargetComponent pkgid cname WholeComponent
renderRunProblem (TargetProblemIsSubComponent pkgid cname subtarget) =
"The run command can only run an executable as a whole, "
++ "not files or modules within them, but the target '"
++ showTargetSelector targetSelector
++ "' refers to "
++ renderTargetSelector targetSelector
++ "."
where
targetSelector = TargetComponent pkgid cname subtarget
targetSelector = TargetComponent pkgid cname
renderRunProblem (TargetProblemNoExes targetSelector) =
"Cannot run the target '"
++ showTargetSelector targetSelector
Expand Down
Loading

0 comments on commit 3f4c81f

Please sign in to comment.