|
| 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 | + ] |
0 commit comments