1 {-# LANGUAGE RecordWildCards #-}
3 -- | cabal-install CLI command: build
4 module Distribution
.Client
.CmdBuild
5 ( -- * The @build@ CLI and action
11 -- * Internals exposed for testing
12 , selectPackageTargets
13 , selectComponentTarget
16 import Distribution
.Client
.Compat
.Prelude
19 import Distribution
.Client
.CmdErrorMessages
20 import Distribution
.Client
.ProjectFlags
21 ( removeIgnoreProjectOption
23 import Distribution
.Client
.ProjectOrchestration
24 import Distribution
.Client
.TargetProblem
29 import qualified Data
.Map
as Map
30 import Distribution
.Client
.Errors
31 import Distribution
.Client
.NixStyleOptions
33 , defaultNixStyleFlags
36 import Distribution
.Client
.ScriptUtils
37 ( AcceptNoTargets
(..)
39 , updateContextAndWriteProjectFile
40 , withContextAndSelectors
42 import Distribution
.Client
.Setup
47 import Distribution
.Simple
.Command
52 import Distribution
.Simple
.Flag
(Flag
(..), fromFlag
, fromFlagOrDefault
, toFlag
)
53 import Distribution
.Simple
.Utils
57 import Distribution
.Verbosity
61 buildCommand
:: CommandUI
(NixStyleFlags BuildFlags
)
64 { commandName
= "v2-build"
65 , commandSynopsis
= "Compile targets within the project."
66 , commandUsage
= usageAlternatives
"v2-build" ["[TARGETS] [FLAGS]"]
67 , commandDescription
= Just
$ \_
->
69 "Build one or more targets from within the project. The available "
70 ++ "targets are the packages in the project as well as individual "
71 ++ "components within those packages, including libraries, executables, "
72 ++ "test-suites or benchmarks. Targets can be specified by name or "
73 ++ "location. If no target is specified then the default is to build "
74 ++ "the package in the current directory.\n\n"
75 ++ "Dependencies are built or rebuilt as necessary. Additional "
76 ++ "configuration flags can be specified on the command line and these "
77 ++ "extend the project configuration from the 'cabal.project', "
78 ++ "'cabal.project.local' and other files."
79 , commandNotes
= Just
$ \pname
->
84 ++ " Build the package in the current directory "
85 ++ "or all packages in the project\n"
88 ++ " v2-build pkgname\n"
89 ++ " Build the package named pkgname in the project\n"
92 ++ " v2-build ./pkgfoo\n"
93 ++ " Build the package in the ./pkgfoo directory\n"
96 ++ " v2-build cname\n"
97 ++ " Build the component named cname in the project\n"
100 ++ " v2-build cname --enable-profiling\n"
101 ++ " Build the component in profiling mode "
102 ++ "(including dependencies as needed)\n"
103 , commandDefaultFlags
= defaultNixStyleFlags defaultBuildFlags
105 removeIgnoreProjectOption
107 ( \showOrParseArgs
->
111 "Instead of performing a full build just run the configure step"
113 (\v flags
-> flags
{buildOnlyConfigure
= v
})
114 (yesNoOpt showOrParseArgs
)
119 data BuildFlags
= BuildFlags
120 { buildOnlyConfigure
:: Flag
Bool
123 defaultBuildFlags
:: BuildFlags
126 { buildOnlyConfigure
= toFlag
False
129 -- | The @build@ command does a lot. It brings the install plan up to date,
130 -- selects that part of the plan needed by the given or implicit targets and
131 -- then executes the plan.
133 -- For more details on how this works, see the module
134 -- "Distribution.Client.ProjectOrchestration"
135 buildAction
:: NixStyleFlags BuildFlags
-> [String] -> GlobalFlags
-> IO ()
136 buildAction flags
@NixStyleFlags
{extraFlags
= buildFlags
, ..} targetStrings globalFlags
=
137 withContextAndSelectors RejectNoTargets Nothing flags targetStrings globalFlags BuildCommand
$ \targetCtx ctx targetSelectors
-> do
138 -- TODO: This flags defaults business is ugly
141 ( buildOnlyConfigure defaultBuildFlags
142 <> buildOnlyConfigure buildFlags
145 | onlyConfigure
= TargetActionConfigure
146 |
otherwise = TargetActionBuild
148 baseCtx
<- case targetCtx
of
149 ProjectContext
-> return ctx
150 GlobalContext
-> return ctx
151 ScriptContext path exemeta
-> updateContextAndWriteProjectFile ctx path exemeta
154 runProjectPreBuildPhase verbosity baseCtx
$ \elaboratedPlan
-> do
155 -- Interpret the targets on the command line as build targets
156 -- (as opposed to say repl or haddock targets).
158 either (reportBuildTargetProblems verbosity
) return $
161 selectComponentTarget
166 let elaboratedPlan
' =
167 pruneInstallPlanToTargets
172 if buildSettingOnlyDeps
(buildSettings baseCtx
)
174 either (reportCannotPruneDependencies verbosity
) return $
175 pruneInstallPlanToDependencies
176 (Map
.keysSet targets
)
178 else return elaboratedPlan
'
180 return (elaboratedPlan
'', targets
)
182 printPlan verbosity baseCtx buildCtx
184 buildOutcomes
<- runProjectBuildPhase verbosity baseCtx buildCtx
185 runProjectPostBuildPhase verbosity baseCtx buildCtx buildOutcomes
187 verbosity
= fromFlagOrDefault normal
(configVerbosity configFlags
)
189 -- | This defines what a 'TargetSelector' means for the @bench@ command.
190 -- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,
191 -- or otherwise classifies the problem.
193 -- For the @build@ command select all components except non-buildable
194 -- and disabled tests\/benchmarks, fail if there are no such
198 -> [AvailableTarget k
]
199 -> Either TargetProblem
' [k
]
200 selectPackageTargets targetSelector targets
201 -- If there are any buildable targets then we select those
202 |
not (null targetsBuildable
) =
203 Right targetsBuildable
204 -- If there are targets but none are buildable then we report those
205 |
not (null targets
) =
206 Left
(TargetProblemNoneEnabled targetSelector targets
')
207 -- If there are no targets at all then we report that
209 Left
(TargetProblemNoTargets targetSelector
)
211 targets
' = forgetTargetsDetail targets
213 selectBuildableTargetsWith
214 (buildable targetSelector
)
217 -- When there's a target filter like "pkg:tests" then we do select tests,
218 -- but if it's just a target like "pkg" then we don't build tests unless
219 -- they are requested by default (i.e. by using --enable-tests)
220 buildable
(TargetPackage _ _ Nothing
) TargetNotRequestedByDefault
= False
221 buildable
(TargetAllPackages Nothing
) TargetNotRequestedByDefault
= False
224 -- | For a 'TargetComponent' 'TargetSelector', check if the component can be
227 -- For the @build@ command we just need the basic checks on being buildable etc.
228 selectComponentTarget
229 :: SubComponentTarget
231 -> Either TargetProblem
' k
232 selectComponentTarget
= selectComponentTargetBasic
234 reportBuildTargetProblems
:: Verbosity
-> [TargetProblem
'] -> IO a
235 reportBuildTargetProblems verbosity problems
=
236 reportTargetProblems verbosity
"build" problems
238 reportCannotPruneDependencies
:: Verbosity
-> CannotPruneDependencies
-> IO a
239 reportCannotPruneDependencies verbosity
=
240 dieWithException verbosity
. ReportCannotPruneDependencies
. renderCannotPruneDependencies