Skip to content

Commit 4f53a2f

Browse files
authored
Merge pull request #9412 from mpickering/wip/external-commands-fixes
Finish off external commands feature
2 parents 6314590 + d8ebb81 commit 4f53a2f

File tree

37 files changed

+587
-66
lines changed

37 files changed

+587
-66
lines changed

Cabal/src/Distribution/Make.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,6 @@ defaultMainHelper :: [String] -> IO ()
9191
defaultMainHelper args = do
9292
command <- commandsRun (globalCommand commands) commands args
9393
case command of
94-
CommandDelegate -> pure ()
9594
CommandHelp help -> printHelp help
9695
CommandList opts -> printOptionsList opts
9796
CommandErrors errs -> printErrors errs
@@ -100,7 +99,6 @@ defaultMainHelper args = do
10099
_
101100
| fromFlag (globalVersion flags) -> printVersion
102101
| fromFlag (globalNumericVersion flags) -> printNumericVersion
103-
CommandDelegate -> pure ()
104102
CommandHelp help -> printHelp help
105103
CommandList opts -> printOptionsList opts
106104
CommandErrors errs -> printErrors errs

Cabal/src/Distribution/Simple.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -170,7 +170,6 @@ defaultMainHelper hooks args = topHandler $ do
170170
args' <- expandResponse args
171171
command <- commandsRun (globalCommand commands) commands args'
172172
case command of
173-
CommandDelegate -> pure ()
174173
CommandHelp help -> printHelp help
175174
CommandList opts -> printOptionsList opts
176175
CommandErrors errs -> printErrors errs
@@ -179,7 +178,6 @@ defaultMainHelper hooks args = topHandler $ do
179178
_
180179
| fromFlag (globalVersion flags) -> printVersion
181180
| fromFlag (globalNumericVersion flags) -> printNumericVersion
182-
CommandDelegate -> pure ()
183181
CommandHelp help -> printHelp help
184182
CommandList opts -> printOptionsList opts
185183
CommandErrors errs -> printErrors errs

Cabal/src/Distribution/Simple/Command.hs

Lines changed: 54 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,8 @@ module Distribution.Simple.Command
4747

4848
-- ** Running commands
4949
, commandsRun
50+
, commandsRunWithFallback
51+
, defaultCommandFallback
5052

5153
-- * Option Fields
5254
, OptionField (..)
@@ -85,15 +87,12 @@ module Distribution.Simple.Command
8587
import Distribution.Compat.Prelude hiding (get)
8688
import Prelude ()
8789

88-
import Control.Exception (try)
8990
import qualified Data.Array as Array
9091
import qualified Data.List as List
9192
import Distribution.Compat.Lens (ALens', (#~), (^#))
9293
import qualified Distribution.GetOpt as GetOpt
9394
import Distribution.ReadE
9495
import Distribution.Simple.Utils
95-
import System.Directory (findExecutable)
96-
import System.Process (callProcess)
9796

9897
data CommandUI flags = CommandUI
9998
{ commandName :: String
@@ -599,13 +598,11 @@ data CommandParse flags
599598
| CommandList [String]
600599
| CommandErrors [String]
601600
| CommandReadyToGo flags
602-
| CommandDelegate
603601
instance Functor CommandParse where
604602
fmap _ (CommandHelp help) = CommandHelp help
605603
fmap _ (CommandList opts) = CommandList opts
606604
fmap _ (CommandErrors errs) = CommandErrors errs
607605
fmap f (CommandReadyToGo flags) = CommandReadyToGo (f flags)
608-
fmap _ CommandDelegate = CommandDelegate
609606

610607
data CommandType = NormalCommand | HiddenCommand
611608
data Command action
@@ -632,27 +629,62 @@ commandAddAction command action =
632629
let flags = mkflags (commandDefaultFlags command)
633630
in action flags args
634631

632+
-- Print suggested command if edit distance is < 5
633+
badCommand :: [Command action] -> String -> CommandParse a
634+
badCommand commands' cname =
635+
case eDists of
636+
[] -> CommandErrors [unErr]
637+
(s : _) ->
638+
CommandErrors
639+
[ unErr
640+
, "Maybe you meant `" ++ s ++ "`?\n"
641+
]
642+
where
643+
eDists =
644+
map fst . List.sortBy (comparing snd) $
645+
[ (cname', dist)
646+
| -- Note that this is not commandNames, so close suggestions will show
647+
-- hidden commands
648+
(Command cname' _ _ _) <- commands'
649+
, let dist = editDistance cname' cname
650+
, dist < 5
651+
]
652+
unErr = "unrecognised command: " ++ cname ++ " (try --help)"
653+
635654
commandsRun
636655
:: CommandUI a
637656
-> [Command action]
638657
-> [String]
639658
-> IO (CommandParse (a, CommandParse action))
640659
commandsRun globalCommand commands args =
660+
commandsRunWithFallback globalCommand commands defaultCommandFallback args
661+
662+
defaultCommandFallback
663+
:: [Command action]
664+
-> String
665+
-> [String]
666+
-> IO (CommandParse action)
667+
defaultCommandFallback commands' name _cmdArgs = pure $ badCommand commands' name
668+
669+
commandsRunWithFallback
670+
:: CommandUI a
671+
-> [Command action]
672+
-> ([Command action] -> String -> [String] -> IO (CommandParse action))
673+
-> [String]
674+
-> IO (CommandParse (a, CommandParse action))
675+
commandsRunWithFallback globalCommand commands defaultCommand args =
641676
case commandParseArgs globalCommand True args of
642-
CommandDelegate -> pure CommandDelegate
643677
CommandHelp help -> pure $ CommandHelp help
644678
CommandList opts -> pure $ CommandList (opts ++ commandNames)
645679
CommandErrors errs -> pure $ CommandErrors errs
646680
CommandReadyToGo (mkflags, args') -> case args' of
647-
("help" : cmdArgs) -> pure $ handleHelpCommand cmdArgs
681+
("help" : cmdArgs) -> handleHelpCommand flags cmdArgs
648682
(name : cmdArgs) -> case lookupCommand name of
649683
[Command _ _ action _] ->
650684
pure $ CommandReadyToGo (flags, action cmdArgs)
651685
_ -> do
652-
mCommand <- findExecutable $ "cabal-" <> name
653-
case mCommand of
654-
Just exec -> callExternal flags exec cmdArgs
655-
Nothing -> pure $ CommandReadyToGo (flags, badCommand name)
686+
final_cmd <- defaultCommand commands' name cmdArgs
687+
return $ CommandReadyToGo (flags, final_cmd)
656688
[] -> pure $ CommandReadyToGo (flags, noCommand)
657689
where
658690
flags = mkflags (commandDefaultFlags globalCommand)
@@ -661,55 +693,29 @@ commandsRun globalCommand commands args =
661693
[ cmd | cmd@(Command cname' _ _ _) <- commands', cname' == cname
662694
]
663695

664-
callExternal :: a -> String -> [String] -> IO (CommandParse (a, CommandParse action))
665-
callExternal flags exec cmdArgs = do
666-
result <- try $ callProcess exec cmdArgs
667-
case result of
668-
Left ex -> pure $ CommandErrors ["Error executing external command: " ++ show (ex :: SomeException)]
669-
Right _ -> pure $ CommandReadyToGo (flags, CommandDelegate)
670-
671696
noCommand = CommandErrors ["no command given (try --help)\n"]
672697

673-
-- Print suggested command if edit distance is < 5
674-
badCommand :: String -> CommandParse a
675-
badCommand cname =
676-
case eDists of
677-
[] -> CommandErrors [unErr]
678-
(s : _) ->
679-
CommandErrors
680-
[ unErr
681-
, "Maybe you meant `" ++ s ++ "`?\n"
682-
]
683-
where
684-
eDists =
685-
map fst . List.sortBy (comparing snd) $
686-
[ (cname', dist)
687-
| (Command cname' _ _ _) <- commands'
688-
, let dist = editDistance cname' cname
689-
, dist < 5
690-
]
691-
unErr = "unrecognised command: " ++ cname ++ " (try --help)"
692-
693698
commands' = commands ++ [commandAddAction helpCommandUI undefined]
694699
commandNames = [name | (Command name _ _ NormalCommand) <- commands']
695700

696701
-- A bit of a hack: support "prog help" as a synonym of "prog --help"
697702
-- furthermore, support "prog help command" as "prog command --help"
698-
handleHelpCommand cmdArgs =
703+
handleHelpCommand flags cmdArgs =
699704
case commandParseArgs helpCommandUI True cmdArgs of
700-
CommandDelegate -> CommandDelegate
701-
CommandHelp help -> CommandHelp help
702-
CommandList list -> CommandList (list ++ commandNames)
703-
CommandErrors _ -> CommandHelp globalHelp
704-
CommandReadyToGo (_, []) -> CommandHelp globalHelp
705+
CommandHelp help -> pure $ CommandHelp help
706+
CommandList list -> pure $ CommandList (list ++ commandNames)
707+
CommandErrors _ -> pure $ CommandHelp globalHelp
708+
CommandReadyToGo (_, []) -> pure $ CommandHelp globalHelp
705709
CommandReadyToGo (_, (name : cmdArgs')) ->
706710
case lookupCommand name of
707711
[Command _ _ action _] ->
708712
case action ("--help" : cmdArgs') of
709-
CommandHelp help -> CommandHelp help
710-
CommandList _ -> CommandList []
711-
_ -> CommandHelp globalHelp
712-
_ -> badCommand name
713+
CommandHelp help -> pure $ CommandHelp help
714+
CommandList _ -> pure $ CommandList []
715+
_ -> pure $ CommandHelp globalHelp
716+
_ -> do
717+
fall_back <- defaultCommand commands' name ("--help" : cmdArgs')
718+
return $ CommandReadyToGo (flags, fall_back)
713719
where
714720
globalHelp = commandHelp globalCommand
715721

cabal-install/src/Distribution/Client/Main.hs

Lines changed: 28 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -205,7 +205,8 @@ import Distribution.Simple.Command
205205
, commandAddAction
206206
, commandFromSpec
207207
, commandShowOptions
208-
, commandsRun
208+
, commandsRunWithFallback
209+
, defaultCommandFallback
209210
, hiddenCommand
210211
)
211212
import Distribution.Simple.Compiler (PackageDBStack)
@@ -221,6 +222,8 @@ import Distribution.Simple.PackageDescription (readGenericPackageDescription)
221222
import Distribution.Simple.Program
222223
( configureAllKnownPrograms
223224
, defaultProgramDb
225+
, defaultProgramSearchPath
226+
, findProgramOnSearchPath
224227
, getProgramInvocationOutput
225228
, simpleProgramInvocation
226229
)
@@ -261,7 +264,7 @@ import System.Directory
261264
, getCurrentDirectory
262265
, withCurrentDirectory
263266
)
264-
import System.Environment (getProgName)
267+
import System.Environment (getEnvironment, getExecutablePath, getProgName)
265268
import System.FilePath
266269
( dropExtension
267270
, splitExtension
@@ -276,6 +279,7 @@ import System.IO
276279
, stderr
277280
, stdout
278281
)
282+
import System.Process (createProcess, env, proc)
279283

280284
-- | Entry point
281285
--
@@ -334,9 +338,8 @@ warnIfAssertionsAreEnabled =
334338
mainWorker :: [String] -> IO ()
335339
mainWorker args = do
336340
topHandler $ do
337-
command <- commandsRun (globalCommand commands) commands args
341+
command <- commandsRunWithFallback (globalCommand commands) commands delegateToExternal args
338342
case command of
339-
CommandDelegate -> pure ()
340343
CommandHelp help -> printGlobalHelp help
341344
CommandList opts -> printOptionsList opts
342345
CommandErrors errs -> printErrors errs
@@ -347,7 +350,6 @@ mainWorker args = do
347350
printVersion
348351
| fromFlagOrDefault False (globalNumericVersion globalFlags) ->
349352
printNumericVersion
350-
CommandDelegate -> pure ()
351353
CommandHelp help -> printCommandHelp help
352354
CommandList opts -> printOptionsList opts
353355
CommandErrors errs -> do
@@ -366,6 +368,27 @@ mainWorker args = do
366368
warnIfAssertionsAreEnabled
367369
action globalFlags
368370
where
371+
delegateToExternal
372+
:: [Command Action]
373+
-> String
374+
-> [String]
375+
-> IO (CommandParse Action)
376+
delegateToExternal commands' name cmdArgs = do
377+
mCommand <- findProgramOnSearchPath normal defaultProgramSearchPath ("cabal-" <> name)
378+
case mCommand of
379+
Just (exec, _) -> return (CommandReadyToGo $ \_ -> callExternal exec name cmdArgs)
380+
Nothing -> defaultCommandFallback commands' name cmdArgs
381+
382+
callExternal :: String -> String -> [String] -> IO ()
383+
callExternal exec name cmdArgs = do
384+
cur_env <- getEnvironment
385+
cabal_exe <- getExecutablePath
386+
let new_env = ("CABAL", cabal_exe) : cur_env
387+
result <- try $ createProcess ((proc exec (name : cmdArgs)){env = Just new_env})
388+
case result of
389+
Left ex -> printErrors ["Error executing external command: " ++ show (ex :: SomeException)]
390+
Right _ -> return ()
391+
369392
printCommandHelp help = do
370393
pname <- getProgName
371394
putStr (help pname)

cabal-install/src/Distribution/Client/SavedFlags.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,6 @@ readCommandFlags :: FilePath -> CommandUI flags -> IO flags
5151
readCommandFlags path command = do
5252
savedArgs <- fmap (fromMaybe []) (readSavedArgs path)
5353
case (commandParseArgs command True savedArgs) of
54-
CommandDelegate -> error "CommandDelegate Flags evaluated, this should never occur"
5554
CommandHelp _ -> throwIO (SavedArgsErrorHelp savedArgs)
5655
CommandList _ -> throwIO (SavedArgsErrorList savedArgs)
5756
CommandErrors errs -> throwIO (SavedArgsErrorOther savedArgs errs)
Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
# cabal v2-build
2+
Resolving dependencies...
3+
Build profile: -w ghc-<GHCVER> -O1
4+
In order, the following will be built:
5+
- setup-test-0.1.0.0 (exe:cabal-aaaa) (first run)
6+
Configuring executable 'cabal-aaaa' for setup-test-0.1.0.0...
7+
Preprocessing executable 'cabal-aaaa' for setup-test-0.1.0.0...
8+
Building executable 'cabal-aaaa' for setup-test-0.1.0.0...
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
packages: setup-test/
Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,47 @@
1+
import Test.Cabal.Prelude
2+
import qualified System.Process as Process
3+
import Control.Concurrent (threadDelay)
4+
import System.Directory (removeFile)
5+
import Control.Exception (catch, throwIO)
6+
import System.IO.Error (isDoesNotExistError)
7+
import qualified Data.Time.Clock as Time
8+
import qualified Data.Time.Format as Time
9+
import Data.Maybe
10+
import System.Environment
11+
import System.FilePath
12+
13+
main = do
14+
cabalTest $ do
15+
res <- cabalWithStdin "v2-build" ["all"] ""
16+
exe_path <- withPlan $ planExePath "setup-test" "cabal-aaaa"
17+
addToPath (takeDirectory exe_path) $ do
18+
-- Test that the thing works at all
19+
res <- cabal_raw_action ["aaaa"] (\h -> () <$ Process.waitForProcess h)
20+
assertOutputContains "aaaa" res
21+
22+
-- Test that the extra arguments are passed on
23+
res <- cabal_raw_action ["aaaa", "--foobaz"] (\h -> () <$ Process.waitForProcess h)
24+
assertOutputContains "--foobaz" res
25+
26+
-- Test what happens with "global" flags
27+
res <- cabal_raw_action ["aaaa", "--version"] (\h -> () <$ Process.waitForProcess h)
28+
assertOutputContains "--version" res
29+
30+
-- Test what happens with "global" flags
31+
res <- cabal_raw_action ["aaaa", "--config-file", "abc"] (\h -> () <$ Process.waitForProcess h)
32+
assertOutputContains "--config-file" res
33+
34+
35+
cabal_raw_action :: [String] -> (Process.ProcessHandle -> IO ()) -> TestM Result
36+
cabal_raw_action args action = do
37+
configured_prog <- requireProgramM cabalProgram
38+
env <- getTestEnv
39+
r <- liftIO $ runAction (testVerbosity env)
40+
(Just (testCurrentDir env))
41+
(testEnvironment env)
42+
(programPath configured_prog)
43+
args
44+
Nothing
45+
action
46+
recordLog r
47+
requireSuccess r
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
module Main where
2+
3+
import System.Environment
4+
5+
main = getArgs >>= print
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
# Revision history for setup-test
2+
3+
## 0.1.0.0 -- YYYY-mm-dd
4+
5+
* First version. Released on an unsuspecting world.

0 commit comments

Comments
 (0)