Add NoImplicitPrelude to buildTypeScript
[cabal.git] / cabal-install / src / Distribution / Client / CmdBuild.hs
blob44f1c4e0f27cab984e1eed6b2d2fe2da4d1d5815
1 {-# LANGUAGE RecordWildCards #-}
3 -- | cabal-install CLI command: build
4 module Distribution.Client.CmdBuild
5 ( -- * The @build@ CLI and action
6 buildCommand
7 , buildAction
8 , BuildFlags (..)
9 , defaultBuildFlags
11 -- * Internals exposed for testing
12 , selectPackageTargets
13 , selectComponentTarget
14 ) where
16 import Distribution.Client.Compat.Prelude
17 import Prelude ()
19 import Distribution.Client.CmdErrorMessages
20 import Distribution.Client.ProjectFlags
21 ( removeIgnoreProjectOption
23 import Distribution.Client.ProjectOrchestration
24 import Distribution.Client.TargetProblem
25 ( TargetProblem (..)
26 , TargetProblem'
29 import qualified Data.Map as Map
30 import Distribution.Client.Errors
31 import Distribution.Client.NixStyleOptions
32 ( NixStyleFlags (..)
33 , defaultNixStyleFlags
34 , nixStyleOptions
36 import Distribution.Client.ScriptUtils
37 ( AcceptNoTargets (..)
38 , TargetContext (..)
39 , updateContextAndWriteProjectFile
40 , withContextAndSelectors
42 import Distribution.Client.Setup
43 ( CommonSetupFlags (..)
44 , ConfigFlags (..)
45 , GlobalFlags
46 , yesNoOpt
48 import Distribution.Simple.Command
49 ( CommandUI (..)
50 , option
51 , usageAlternatives
53 import Distribution.Simple.Flag (Flag (..), fromFlag, fromFlagOrDefault, toFlag)
54 import Distribution.Simple.Utils
55 ( dieWithException
56 , wrapText
58 import Distribution.Verbosity
59 ( normal
62 buildCommand :: CommandUI (NixStyleFlags BuildFlags)
63 buildCommand =
64 CommandUI
65 { commandName = "v2-build"
66 , commandSynopsis = "Compile targets within the project."
67 , commandUsage = usageAlternatives "v2-build" ["[TARGETS] [FLAGS]"]
68 , commandDescription = Just $ \_ ->
69 wrapText $
70 "Build one or more targets from within the project. The available "
71 ++ "targets are the packages in the project as well as individual "
72 ++ "components within those packages, including libraries, executables, "
73 ++ "test-suites or benchmarks. Targets can be specified by name or "
74 ++ "location. If no target is specified then the default is to build "
75 ++ "the package in the current directory.\n\n"
76 ++ "Dependencies are built or rebuilt as necessary. Additional "
77 ++ "configuration flags can be specified on the command line and these "
78 ++ "extend the project configuration from the 'cabal.project', "
79 ++ "'cabal.project.local' and other files."
80 , commandNotes = Just $ \pname ->
81 "Examples:\n"
82 ++ " "
83 ++ pname
84 ++ " v2-build\n"
85 ++ " Build the package in the current directory "
86 ++ "or all packages in the project\n"
87 ++ " "
88 ++ pname
89 ++ " v2-build pkgname\n"
90 ++ " Build the package named pkgname in the project\n"
91 ++ " "
92 ++ pname
93 ++ " v2-build ./pkgfoo\n"
94 ++ " Build the package in the ./pkgfoo directory\n"
95 ++ " "
96 ++ pname
97 ++ " v2-build cname\n"
98 ++ " Build the component named cname in the project\n"
99 ++ " "
100 ++ pname
101 ++ " v2-build cname --enable-profiling\n"
102 ++ " Build the component in profiling mode "
103 ++ "(including dependencies as needed)\n"
104 , commandDefaultFlags = defaultNixStyleFlags defaultBuildFlags
105 , commandOptions =
106 removeIgnoreProjectOption
107 . nixStyleOptions
108 ( \showOrParseArgs ->
109 [ option
111 ["only-configure"]
112 "Instead of performing a full build just run the configure step"
113 buildOnlyConfigure
114 (\v flags -> flags{buildOnlyConfigure = v})
115 (yesNoOpt showOrParseArgs)
120 data BuildFlags = BuildFlags
121 { buildOnlyConfigure :: Flag Bool
124 defaultBuildFlags :: BuildFlags
125 defaultBuildFlags =
126 BuildFlags
127 { buildOnlyConfigure = toFlag False
130 -- | The @build@ command does a lot. It brings the install plan up to date,
131 -- selects that part of the plan needed by the given or implicit targets and
132 -- then executes the plan.
134 -- For more details on how this works, see the module
135 -- "Distribution.Client.ProjectOrchestration"
136 buildAction :: NixStyleFlags BuildFlags -> [String] -> GlobalFlags -> IO ()
137 buildAction flags@NixStyleFlags{extraFlags = buildFlags, ..} targetStrings globalFlags =
138 withContextAndSelectors RejectNoTargets Nothing flags targetStrings globalFlags BuildCommand $ \targetCtx ctx targetSelectors -> do
139 -- TODO: This flags defaults business is ugly
140 let onlyConfigure =
141 fromFlag
142 ( buildOnlyConfigure defaultBuildFlags
143 <> buildOnlyConfigure buildFlags
145 targetAction
146 | onlyConfigure = TargetActionConfigure
147 | otherwise = TargetActionBuild
149 baseCtx <- case targetCtx of
150 ProjectContext -> return ctx
151 GlobalContext -> return ctx
152 ScriptContext path exemeta -> updateContextAndWriteProjectFile ctx path exemeta
154 buildCtx <-
155 runProjectPreBuildPhase verbosity baseCtx $ \elaboratedPlan -> do
156 -- Interpret the targets on the command line as build targets
157 -- (as opposed to say repl or haddock targets).
158 targets <-
159 either (reportBuildTargetProblems verbosity) return $
160 resolveTargets
161 selectPackageTargets
162 selectComponentTarget
163 elaboratedPlan
164 Nothing
165 targetSelectors
167 let elaboratedPlan' =
168 pruneInstallPlanToTargets
169 targetAction
170 targets
171 elaboratedPlan
172 elaboratedPlan'' <-
173 if buildSettingOnlyDeps (buildSettings baseCtx)
174 then
175 either (reportCannotPruneDependencies verbosity) return $
176 pruneInstallPlanToDependencies
177 (Map.keysSet targets)
178 elaboratedPlan'
179 else return elaboratedPlan'
181 return (elaboratedPlan'', targets)
183 printPlan verbosity baseCtx buildCtx
185 buildOutcomes <- runProjectBuildPhase verbosity baseCtx buildCtx
186 runProjectPostBuildPhase verbosity baseCtx buildCtx buildOutcomes
187 where
188 verbosity = fromFlagOrDefault normal (setupVerbosity $ configCommonFlags configFlags)
190 -- | This defines what a 'TargetSelector' means for the @bench@ command.
191 -- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,
192 -- or otherwise classifies the problem.
194 -- For the @build@ command select all components except non-buildable
195 -- and disabled tests\/benchmarks, fail if there are no such
196 -- components
197 selectPackageTargets
198 :: TargetSelector
199 -> [AvailableTarget k]
200 -> Either TargetProblem' [k]
201 selectPackageTargets targetSelector targets
202 -- If there are any buildable targets then we select those
203 | not (null targetsBuildable) =
204 Right targetsBuildable
205 -- If there are targets but none are buildable then we report those
206 | not (null targets) =
207 Left (TargetProblemNoneEnabled targetSelector targets')
208 -- If there are no targets at all then we report that
209 | otherwise =
210 Left (TargetProblemNoTargets targetSelector)
211 where
212 targets' = forgetTargetsDetail targets
213 targetsBuildable =
214 selectBuildableTargetsWith
215 (buildable targetSelector)
216 targets
218 -- When there's a target filter like "pkg:tests" then we do select tests,
219 -- but if it's just a target like "pkg" then we don't build tests unless
220 -- they are requested by default (i.e. by using --enable-tests)
221 buildable (TargetPackage _ _ Nothing) TargetNotRequestedByDefault = False
222 buildable (TargetAllPackages Nothing) TargetNotRequestedByDefault = False
223 buildable _ _ = True
225 -- | For a 'TargetComponent' 'TargetSelector', check if the component can be
226 -- selected.
228 -- For the @build@ command we just need the basic checks on being buildable etc.
229 selectComponentTarget
230 :: SubComponentTarget
231 -> AvailableTarget k
232 -> Either TargetProblem' k
233 selectComponentTarget = selectComponentTargetBasic
235 reportBuildTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
236 reportBuildTargetProblems verbosity problems =
237 reportTargetProblems verbosity "build" problems
239 reportCannotPruneDependencies :: Verbosity -> CannotPruneDependencies -> IO a
240 reportCannotPruneDependencies verbosity =
241 dieWithException verbosity . ReportCannotPruneDependencies . renderCannotPruneDependencies