1
+ {-# LANGUAGE RecordWildCards #-}
1
2
-- | cabal-install CLI command: show-build-info
2
3
--
3
4
module Distribution.Client.CmdShowBuildInfo (
@@ -10,14 +11,13 @@ import Distribution.Client.Compat.Prelude
10
11
( when , find , fromMaybe )
11
12
import Distribution.Client.ProjectOrchestration
12
13
import Distribution.Client.CmdErrorMessages
13
- import Distribution.Client.CmdInstall.ClientInstallFlags
14
+ import Distribution.Client.TargetProblem
15
+ ( TargetProblem (.. ), TargetProblem' )
14
16
15
17
import Distribution.Client.Setup
16
- ( GlobalFlags , ConfigFlags (.. ), ConfigExFlags , InstallFlags )
17
- import qualified Distribution.Client.Setup as Client
18
+ ( GlobalFlags )
18
19
import Distribution.Simple.Setup
19
- ( HaddockFlags , TestFlags , BenchmarkFlags
20
- , fromFlagOrDefault )
20
+ (configVerbosity , fromFlagOrDefault )
21
21
import Distribution.Simple.Command
22
22
( CommandUI (.. ), option , reqArg' , usageAlternatives )
23
23
import Distribution.Verbosity
@@ -30,8 +30,8 @@ import Distribution.Types.Version
30
30
( mkVersion )
31
31
import Distribution.Types.PackageDescription
32
32
( buildType )
33
- import Distribution.Deprecated.Text
34
- ( display )
33
+ import Distribution.Pretty
34
+ ( prettyShow )
35
35
36
36
import qualified Data.Map as Map
37
37
import qualified Distribution.Simple.Setup as Cabal
@@ -43,6 +43,8 @@ import Distribution.Client.ProjectPlanning.Types
43
43
import Distribution.Client.ProjectPlanning
44
44
( setupHsConfigureFlags , setupHsConfigureArgs , setupHsBuildFlags
45
45
, setupHsBuildArgs , setupHsScriptOptions )
46
+ import Distribution.Client.NixStyleOptions
47
+ ( NixStyleFlags (.. ), nixStyleOptions , defaultNixStyleFlags )
46
48
import Distribution.Client.DistDirLayout
47
49
( distBuildDirectory )
48
50
import Distribution.Client.Types
@@ -51,15 +53,14 @@ import Distribution.Client.JobControl
51
53
( newLock , Lock )
52
54
import Distribution.Simple.Configure
53
55
( tryGetPersistBuildConfig )
54
- import qualified Distribution.Client.CmdInstall as CmdInstall
55
56
56
57
import System.Directory
57
58
( getTemporaryDirectory )
58
59
import System.FilePath
59
60
( (</>) )
60
61
61
- showBuildInfoCommand :: CommandUI ShowBuildInfoFlags
62
- showBuildInfoCommand = CmdInstall. installCommand {
62
+ showBuildInfoCommand :: CommandUI ( NixStyleFlags ShowBuildInfoFlags )
63
+ showBuildInfoCommand = CommandUI {
63
64
commandName = " show-build-info" ,
64
65
commandSynopsis = " Show project build information" ,
65
66
commandUsage = usageAlternatives " show-build-info" [ " [TARGETS] [FLAGS]" ],
@@ -75,9 +76,7 @@ showBuildInfoCommand = CmdInstall.installCommand {
75
76
++ " " ++ pname ++ " show-build-info ./pkgname \n "
76
77
++ " Shows build information about the package located in './pkgname'\n "
77
78
++ cmdCommonHelpTextNewBuildBeta,
78
- commandOptions = \ showOrParseArgs ->
79
- Client. liftOptions buildInfoInstallCommandFlags (\ pf flags -> flags { buildInfoInstallCommandFlags = pf }) (commandOptions CmdInstall. installCommand showOrParseArgs)
80
- ++
79
+ commandOptions = nixStyleOptions $ \ _ ->
81
80
[ option [] [" buildinfo-json-output" ]
82
81
" Write the result to the given file instead of stdout"
83
82
buildInfoOutputFile (\ pf flags -> flags { buildInfoOutputFile = pf })
@@ -87,28 +86,25 @@ showBuildInfoCommand = CmdInstall.installCommand {
87
86
buildInfoUnitIds (\ pf flags -> flags { buildInfoUnitIds = pf })
88
87
(reqArg' " UNIT-ID" (Just . words ) (fromMaybe [] ))
89
88
],
90
- commandDefaultFlags = defaultShowBuildInfoFlags
91
-
92
- }
89
+ commandDefaultFlags = defaultNixStyleFlags defaultShowBuildInfoFlags
90
+ }
93
91
94
92
data ShowBuildInfoFlags = ShowBuildInfoFlags
95
- { buildInfoInstallCommandFlags :: (ConfigFlags , ConfigExFlags , InstallFlags , HaddockFlags , TestFlags , BenchmarkFlags , ClientInstallFlags )
96
- , buildInfoOutputFile :: Maybe FilePath
93
+ { buildInfoOutputFile :: Maybe FilePath
97
94
, buildInfoUnitIds :: Maybe [String ]
98
95
}
99
96
100
97
defaultShowBuildInfoFlags :: ShowBuildInfoFlags
101
98
defaultShowBuildInfoFlags = ShowBuildInfoFlags
102
- { buildInfoInstallCommandFlags = (mempty , mempty , mempty , mempty , mempty , mempty , mempty )
103
- , buildInfoOutputFile = Nothing
99
+ { buildInfoOutputFile = Nothing
104
100
, buildInfoUnitIds = Nothing
105
101
}
106
102
107
103
-- | The @show-build-info@ exports information about a package and the compiler
108
104
-- configuration used to build it as JSON, that can be used by other tooling.
109
105
-- See "Distribution.Simple.ShowBuildInfo" for more information.
110
- showBuildInfoAction :: ShowBuildInfoFlags -> [String ] -> GlobalFlags -> IO ()
111
- showBuildInfoAction ( ShowBuildInfoFlags (configFlags, configExFlags, installFlags, haddockFlags, testFlags, benchmarkFlags, clientInstallFlags) fileOutput unitIds)
106
+ showBuildInfoAction :: NixStyleFlags ShowBuildInfoFlags -> [String ] -> GlobalFlags -> IO ()
107
+ showBuildInfoAction flags @ NixStyleFlags { extraFlags = ( ShowBuildInfoFlags fileOutput unitIds), .. }
112
108
targetStrings globalFlags = do
113
109
baseCtx <- establishProjectBaseContext verbosity cliConfig OtherCommand
114
110
let baseCtx' = baseCtx
@@ -122,11 +118,10 @@ showBuildInfoAction (ShowBuildInfoFlags (configFlags, configExFlags, installFlag
122
118
runProjectPreBuildPhase verbosity baseCtx' $ \ elaboratedPlan -> do
123
119
-- Interpret the targets on the command line as build targets
124
120
-- (as opposed to say repl or haddock targets).
125
- targets <- either (reportTargetProblems verbosity) return
121
+ targets <- either (reportShowBuildInfoTargetProblems verbosity) return
126
122
$ resolveTargets
127
123
selectPackageTargets
128
124
selectComponentTarget
129
- TargetProblemCommon
130
125
elaboratedPlan
131
126
Nothing
132
127
targetSelectors
@@ -139,12 +134,8 @@ showBuildInfoAction (ShowBuildInfoFlags (configFlags, configExFlags, installFlag
139
134
where
140
135
-- Default to silent verbosity otherwise it will pollute our json output
141
136
verbosity = fromFlagOrDefault silent (configVerbosity configFlags)
142
- cliConfig = commandLineFlagsToProjectConfig
143
- globalFlags configFlags configExFlags
144
- installFlags clientInstallFlags
145
- haddockFlags
146
- testFlags
147
- benchmarkFlags
137
+ cliConfig = commandLineFlagsToProjectConfig globalFlags flags
138
+ mempty -- ClientInstallFlags, not needed here
148
139
149
140
-- Pretty nasty piecemeal out of json, but I can't see a way to retrieve output of the setupWrapper'd tasks
150
141
showTargets :: Maybe FilePath -> Maybe [String ] -> Verbosity -> ProjectBaseContext -> ProjectBuildContext -> Lock -> IO ()
@@ -187,12 +178,12 @@ showTargets fileOutput unitIds verbosity baseCtx buildCtx lock = do
187
178
printer " ]"
188
179
189
180
unitIdToFilePath :: UnitId -> FilePath
190
- unitIdToFilePath unitId = " build-info-" ++ display unitId ++ " .json"
181
+ unitIdToFilePath unitId = " build-info-" ++ prettyShow unitId ++ " .json"
191
182
192
183
showInfo :: FilePath -> Verbosity -> ProjectBaseContext -> ProjectBuildContext -> Lock -> [ElaboratedConfiguredPackage ] -> UnitId -> IO ()
193
184
showInfo fileOutput verbosity baseCtx buildCtx lock pkgs targetUnitId =
194
185
case mbPkg of
195
- Nothing -> die' verbosity $ " No unit " ++ display targetUnitId
186
+ Nothing -> die' verbosity $ " No unit " ++ prettyShow targetUnitId
196
187
Just pkg -> do
197
188
let shared = elaboratedShared buildCtx
198
189
install = elaboratedPlanOriginal buildCtx
@@ -221,8 +212,8 @@ showInfo fileOutput verbosity baseCtx buildCtx lock pkgs targetUnitId =
221
212
(elabPkgDescription pkg) buildType'
222
213
when (cabalVersion < mkVersion [3 , 0 , 0 , 0 ])
223
214
( die' verbosity $ " Only a Cabal version >= 3.0.0.0 is supported for this command.\n "
224
- ++ " Found version: " ++ display cabalVersion ++ " \n "
225
- ++ " For component: " ++ display targetUnitId
215
+ ++ " Found version: " ++ prettyShow cabalVersion ++ " \n "
216
+ ++ " For component: " ++ prettyShow targetUnitId
226
217
)
227
218
-- Configure the package if there's no existing config
228
219
lbi <- tryGetPersistBuildConfig buildDir
@@ -260,7 +251,7 @@ showInfo fileOutput verbosity baseCtx buildCtx lock pkgs targetUnitId =
260
251
-- tests\/benchmarks, fail if there are no such components
261
252
--
262
253
selectPackageTargets :: TargetSelector
263
- -> [AvailableTarget k ] -> Either TargetProblem [k ]
254
+ -> [AvailableTarget k ] -> Either TargetProblem' [k ]
264
255
selectPackageTargets targetSelector targets
265
256
266
257
-- If there are any buildable targets then we select those
@@ -293,33 +284,10 @@ selectPackageTargets targetSelector targets
293
284
-- For the @show-build-info@ command we just need the basic checks on being buildable etc.
294
285
--
295
286
selectComponentTarget :: SubComponentTarget
296
- -> AvailableTarget k -> Either TargetProblem k
297
- selectComponentTarget subtarget =
298
- either (Left . TargetProblemCommon ) Right
299
- . selectComponentTargetBasic subtarget
300
-
301
-
302
- -- | The various error conditions that can occur when matching a
303
- -- 'TargetSelector' against 'AvailableTarget's for the @show-build-info@ command.
304
- --
305
- data TargetProblem =
306
- TargetProblemCommon TargetProblemCommon
307
-
308
- -- | The 'TargetSelector' matches targets but none are buildable
309
- | TargetProblemNoneEnabled TargetSelector [AvailableTarget () ]
310
-
311
- -- | There are no targets at all
312
- | TargetProblemNoTargets TargetSelector
313
- deriving (Eq , Show )
287
+ -> AvailableTarget k -> Either TargetProblem' k
288
+ selectComponentTarget = selectComponentTargetBasic
314
289
315
- reportTargetProblems :: Verbosity -> [TargetProblem ] -> IO a
316
- reportTargetProblems verbosity =
317
- die' verbosity . unlines . map renderTargetProblem
318
290
319
- renderTargetProblem :: TargetProblem -> String
320
- renderTargetProblem (TargetProblemCommon problem) =
321
- renderTargetProblemCommon " show-build-info" problem
322
- renderTargetProblem (TargetProblemNoneEnabled targetSelector targets) =
323
- renderTargetProblemNoneEnabled " show-build-info" targetSelector targets
324
- renderTargetProblem(TargetProblemNoTargets targetSelector) =
325
- renderTargetProblemNoTargets " show-build-info" targetSelector
291
+ reportShowBuildInfoTargetProblems :: Verbosity -> [TargetProblem' ] -> IO a
292
+ reportShowBuildInfoTargetProblems verbosity problems =
293
+ reportTargetProblems verbosity " show-build-info" problems
0 commit comments