Skip to content

Commit 7a0000d

Browse files
authored
Merge pull request #6457 from phadej/v2-run-z
Add --ignore-project flag to v2-run
2 parents 7fd2f60 + e63a705 commit 7a0000d

File tree

5 files changed

+127
-42
lines changed

5 files changed

+127
-42
lines changed

cabal-dev-scripts/src/Preprocessor.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
{- cabal:
2+
build-depends: base, containers
3+
-}
14
{-# LANGUAGE DeriveFunctor #-}
25
module Main (main) where
36

cabal-install/Distribution/Client/CmdRun.hs

Lines changed: 83 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -23,15 +23,20 @@ import Distribution.Client.Compat.Prelude hiding (toList)
2323
import Distribution.Client.ProjectOrchestration
2424
import Distribution.Client.CmdErrorMessages
2525

26+
import Distribution.Client.CmdRun.ClientRunFlags
27+
2628
import Distribution.Client.Setup
27-
( GlobalFlags(..), ConfigFlags(..), ConfigExFlags, InstallFlags )
29+
( GlobalFlags(..), ConfigFlags(..), ConfigExFlags, InstallFlags(..)
30+
, configureExOptions, haddockOptions, installOptions, testOptions
31+
, benchmarkOptions, configureOptions, liftOptions )
32+
import Distribution.Solver.Types.ConstraintSource
33+
( ConstraintSource(..) )
2834
import Distribution.Client.GlobalFlags
2935
( defaultGlobalFlags )
30-
import qualified Distribution.Client.Setup as Client
3136
import Distribution.Simple.Setup
3237
( HaddockFlags, TestFlags, BenchmarkFlags, fromFlagOrDefault )
3338
import Distribution.Simple.Command
34-
( CommandUI(..), usageAlternatives )
39+
( CommandUI(..), OptionField (..), usageAlternatives )
3540
import Distribution.Types.ComponentName
3641
( showComponentName )
3742
import Distribution.Deprecated.Text
@@ -45,7 +50,7 @@ import Distribution.Client.CmdInstall
4550
( establishDummyProjectBaseContext )
4651
import Distribution.Client.ProjectConfig
4752
( ProjectConfig(..), ProjectConfigShared(..)
48-
, withProjectOrGlobalConfig )
53+
, withProjectOrGlobalConfigIgn )
4954
import Distribution.Client.ProjectPlanning
5055
( ElaboratedConfiguredPackage(..)
5156
, ElaboratedInstallPlan, binDirectoryFor )
@@ -109,43 +114,74 @@ import System.FilePath
109114

110115
runCommand :: CommandUI ( ConfigFlags, ConfigExFlags, InstallFlags
111116
, HaddockFlags, TestFlags, BenchmarkFlags
117+
, ClientRunFlags
112118
)
113-
runCommand = Client.installCommand {
114-
commandName = "v2-run",
115-
commandSynopsis = "Run an executable.",
116-
commandUsage = usageAlternatives "v2-run"
117-
[ "[TARGET] [FLAGS] [-- EXECUTABLE_FLAGS]" ],
118-
commandDescription = Just $ \pname -> wrapText $
119-
"Runs the specified executable-like component (an executable, a test, "
120-
++ "or a benchmark), first ensuring it is up to date.\n\n"
121-
122-
++ "Any executable-like component in any package in the project can be "
123-
++ "specified. A package can be specified if contains just one "
124-
++ "executable-like. The default is to use the package in the current "
125-
++ "directory if it contains just one executable-like.\n\n"
126-
127-
++ "Extra arguments can be passed to the program, but use '--' to "
128-
++ "separate arguments for the program from arguments for " ++ pname
129-
++ ". The executable is run in an environment where it can find its "
130-
++ "data files inplace in the build tree.\n\n"
131-
132-
++ "Dependencies are built or rebuilt as necessary. Additional "
133-
++ "configuration flags can be specified on the command line and these "
134-
++ "extend the project configuration from the 'cabal.project', "
135-
++ "'cabal.project.local' and other files.",
136-
commandNotes = Just $ \pname ->
137-
"Examples:\n"
138-
++ " " ++ pname ++ " v2-run\n"
139-
++ " Run the executable-like in the package in the current directory\n"
140-
++ " " ++ pname ++ " v2-run foo-tool\n"
141-
++ " Run the named executable-like (in any package in the project)\n"
142-
++ " " ++ pname ++ " v2-run pkgfoo:foo-tool\n"
143-
++ " Run the executable-like 'foo-tool' in the package 'pkgfoo'\n"
144-
++ " " ++ pname ++ " v2-run foo -O2 -- dothing --fooflag\n"
145-
++ " Build with '-O2' and run the program, passing it extra arguments.\n\n"
146-
147-
++ cmdCommonHelpTextNewBuildBeta
119+
runCommand = CommandUI
120+
{ commandName = "v2-run"
121+
, commandSynopsis = "Run an executable."
122+
, commandUsage = usageAlternatives "v2-run"
123+
[ "[TARGET] [FLAGS] [-- EXECUTABLE_FLAGS]" ]
124+
, commandDescription = Just $ \pname -> wrapText $
125+
"Runs the specified executable-like component (an executable, a test, "
126+
++ "or a benchmark), first ensuring it is up to date.\n\n"
127+
128+
++ "Any executable-like component in any package in the project can be "
129+
++ "specified. A package can be specified if contains just one "
130+
++ "executable-like. The default is to use the package in the current "
131+
++ "directory if it contains just one executable-like.\n\n"
132+
133+
++ "Extra arguments can be passed to the program, but use '--' to "
134+
++ "separate arguments for the program from arguments for " ++ pname
135+
++ ". The executable is run in an environment where it can find its "
136+
++ "data files inplace in the build tree.\n\n"
137+
138+
++ "Dependencies are built or rebuilt as necessary. Additional "
139+
++ "configuration flags can be specified on the command line and these "
140+
++ "extend the project configuration from the 'cabal.project', "
141+
++ "'cabal.project.local' and other files."
142+
, commandNotes = Just $ \pname ->
143+
"Examples:\n"
144+
++ " " ++ pname ++ " v2-run\n"
145+
++ " Run the executable-like in the package in the current directory\n"
146+
++ " " ++ pname ++ " v2-run foo-tool\n"
147+
++ " Run the named executable-like (in any package in the project)\n"
148+
++ " " ++ pname ++ " v2-run pkgfoo:foo-tool\n"
149+
++ " Run the executable-like 'foo-tool' in the package 'pkgfoo'\n"
150+
++ " " ++ pname ++ " v2-run foo -O2 -- dothing --fooflag\n"
151+
++ " Build with '-O2' and run the program, passing it extra arguments.\n\n"
152+
153+
++ cmdCommonHelpTextNewBuildBeta
154+
, commandDefaultFlags = (mempty, mempty, mempty, mempty, mempty, mempty, mempty)
155+
, commandOptions = \showOrParseArgs ->
156+
liftOptions get1 set1
157+
-- Note: [Hidden Flags]
158+
-- hide "constraint", "dependency", and
159+
-- "exact-configuration" from the configure options.
160+
(filter ((`notElem` ["constraint", "dependency"
161+
, "exact-configuration"])
162+
. optionName) $
163+
configureOptions showOrParseArgs)
164+
++ liftOptions get2 set2 (configureExOptions showOrParseArgs ConstraintSourceCommandlineFlag)
165+
++ liftOptions get3 set3
166+
-- hide "target-package-db" flag from the
167+
-- install options.
168+
(filter ((`notElem` ["target-package-db"])
169+
. optionName) $
170+
installOptions showOrParseArgs)
171+
++ liftOptions get4 set4 (haddockOptions showOrParseArgs)
172+
++ liftOptions get5 set5 (testOptions showOrParseArgs)
173+
++ liftOptions get6 set6 (benchmarkOptions showOrParseArgs)
174+
++ liftOptions get7 set7 (clientRunOptions showOrParseArgs)
148175
}
176+
where
177+
get1 (a,_,_,_,_,_,_) = a; set1 a (_,b,c,d,e,f,g) = (a,b,c,d,e,f,g)
178+
get2 (_,b,_,_,_,_,_) = b; set2 b (a,_,c,d,e,f,g) = (a,b,c,d,e,f,g)
179+
get3 (_,_,c,_,_,_,_) = c; set3 c (a,b,_,d,e,f,g) = (a,b,c,d,e,f,g)
180+
get4 (_,_,_,d,_,_,_) = d; set4 d (a,b,c,_,e,f,g) = (a,b,c,d,e,f,g)
181+
get5 (_,_,_,_,e,_,_) = e; set5 e (a,b,c,d,_,f,g) = (a,b,c,d,e,f,g)
182+
get6 (_,_,_,_,_,f,_) = f; set6 f (a,b,c,d,e,_,g) = (a,b,c,d,e,f,g)
183+
get7 (_,_,_,_,_,_,g) = g; set7 g (a,b,c,d,e,f,_) = (a,b,c,d,e,f,g)
184+
149185

150186
-- | The @run@ command runs a specified executable-like component, building it
151187
-- first if necessary. The component can be either an executable, a test,
@@ -156,10 +192,12 @@ runCommand = Client.installCommand {
156192
-- "Distribution.Client.ProjectOrchestration"
157193
--
158194
runAction :: ( ConfigFlags, ConfigExFlags, InstallFlags
159-
, HaddockFlags, TestFlags, BenchmarkFlags )
195+
, HaddockFlags, TestFlags, BenchmarkFlags
196+
, ClientRunFlags )
160197
-> [String] -> GlobalFlags -> IO ()
161198
runAction ( configFlags, configExFlags, installFlags
162-
, haddockFlags, testFlags, benchmarkFlags )
199+
, haddockFlags, testFlags, benchmarkFlags
200+
, clientRunFlags )
163201
targetStrings globalFlags = do
164202
globalTmp <- getTemporaryDirectory
165203
tempDir <- createTempDirectory globalTmp "cabal-repl."
@@ -170,7 +208,10 @@ runAction ( configFlags, configExFlags, installFlags
170208
without config =
171209
establishDummyProjectBaseContext verbosity (config <> cliConfig) tempDir [] OtherCommand
172210

173-
baseCtx <- withProjectOrGlobalConfig verbosity globalConfigFlag with without
211+
let
212+
ignoreProject = fromFlagOrDefault False (crunIgnoreProject clientRunFlags)
213+
214+
baseCtx <- withProjectOrGlobalConfigIgn ignoreProject verbosity globalConfigFlag with without
174215

175216
let
176217
scriptOrError script err = do
Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
{-# LANGUAGE DeriveGeneric #-}
2+
{-# LANGUAGE LambdaCase #-}
3+
module Distribution.Client.CmdRun.ClientRunFlags
4+
( ClientRunFlags(..)
5+
, defaultClientRunFlags
6+
, clientRunOptions
7+
) where
8+
9+
import Distribution.Client.Compat.Prelude
10+
11+
import Distribution.Simple.Command (OptionField (..), ShowOrParseArgs (..), option)
12+
import Distribution.Simple.Setup (Flag (..), toFlag, trueArg)
13+
14+
data ClientRunFlags = ClientRunFlags
15+
{ crunIgnoreProject :: Flag Bool
16+
} deriving (Eq, Show, Generic)
17+
18+
instance Monoid ClientRunFlags where
19+
mempty = gmempty
20+
mappend = (<>)
21+
22+
instance Semigroup ClientRunFlags where
23+
(<>) = gmappend
24+
25+
instance Binary ClientRunFlags
26+
instance Structured ClientRunFlags
27+
28+
defaultClientRunFlags :: ClientRunFlags
29+
defaultClientRunFlags = ClientRunFlags
30+
{ crunIgnoreProject = toFlag False
31+
}
32+
33+
clientRunOptions :: ShowOrParseArgs -> [OptionField ClientRunFlags]
34+
clientRunOptions _ =
35+
[ option "z" ["ignore-project"]
36+
"Ignore local project configuration"
37+
crunIgnoreProject (\v flags -> flags { crunIgnoreProject = v })
38+
trueArg
39+
]

cabal-install/cabal-install.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -177,6 +177,7 @@ executable cabal
177177
Distribution.Client.CmdInstall.ClientInstallFlags
178178
Distribution.Client.CmdRepl
179179
Distribution.Client.CmdRun
180+
Distribution.Client.CmdRun.ClientRunFlags
180181
Distribution.Client.CmdTest
181182
Distribution.Client.CmdLegacy
182183
Distribution.Client.CmdSdist

cabal-install/cabal-install.cabal.pp

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -108,6 +108,7 @@
108108
Distribution.Client.CmdInstall.ClientInstallFlags
109109
Distribution.Client.CmdRepl
110110
Distribution.Client.CmdRun
111+
Distribution.Client.CmdRun.ClientRunFlags
111112
Distribution.Client.CmdTest
112113
Distribution.Client.CmdLegacy
113114
Distribution.Client.CmdSdist

0 commit comments

Comments
 (0)