Skip to content

Commit cc3ccda

Browse files
authored
Merge pull request #10531 from haskell/mergify/bp/3.14/pr-10486
Backport #10486: Catch exception if git is not installed
2 parents 460375d + 30f2bd2 commit cc3ccda

File tree

5 files changed

+50
-11
lines changed

5 files changed

+50
-11
lines changed

cabal-install/src/Distribution/Client/Init/NonInteractive/Heuristics.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -165,14 +165,14 @@ guessAuthorEmail = guessGitInfo "user.email"
165165

166166
guessGitInfo :: Interactive m => String -> m (Maybe String)
167167
guessGitInfo target = do
168-
localInfo <- readProcessWithExitCode "git" ["config", "--local", target] ""
169-
if null $ snd' localInfo
170-
then do
171-
globalInfo <- readProcessWithExitCode "git" ["config", "--global", target] ""
172-
case fst' globalInfo of
173-
ExitSuccess -> return $ Just (trim $ snd' globalInfo)
174-
_ -> return Nothing
175-
else return $ Just (trim $ snd' localInfo)
176-
where
177-
fst' (x, _, _) = x
178-
snd' (_, x, _) = x
168+
localInfo <- maybeReadProcessWithExitCode "git" ["config", "--local", target] ""
169+
case localInfo of
170+
Nothing -> return Nothing
171+
Just (_, localStdout, _) ->
172+
if null localStdout
173+
then do
174+
globalInfo <- maybeReadProcessWithExitCode "git" ["config", "--global", target] ""
175+
case globalInfo of
176+
Just (ExitSuccess, globalStdout, _) -> return $ Just (trim globalStdout)
177+
_ -> return Nothing
178+
else return $ Just (trim localStdout)

cabal-install/src/Distribution/Client/Init/Types.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE DeriveGeneric #-}
44
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
55
{-# LANGUAGE LambdaCase #-}
6+
{-# LANGUAGE TypeApplications #-}
67

78
-- |
89
-- Module : Distribution.Client.Init.Types
@@ -346,6 +347,7 @@ class Monad m => Interactive m where
346347
doesFileExist :: FilePath -> m Bool
347348
canonicalizePathNoThrow :: FilePath -> m FilePath
348349
readProcessWithExitCode :: FilePath -> [String] -> String -> m (ExitCode, String, String)
350+
maybeReadProcessWithExitCode :: FilePath -> [String] -> String -> m (Maybe (ExitCode, String, String))
349351
getEnvironment :: m [(String, String)]
350352
getCurrentYear :: m Integer
351353
listFilesInside :: (FilePath -> m Bool) -> FilePath -> m [FilePath]
@@ -389,6 +391,7 @@ instance Interactive PromptIO where
389391
doesFileExist = liftIO <$> P.doesFileExist
390392
canonicalizePathNoThrow = liftIO <$> P.canonicalizePathNoThrow
391393
readProcessWithExitCode a b c = liftIO $ Process.readProcessWithExitCode a b c
394+
maybeReadProcessWithExitCode a b c = liftIO $ (Just <$> Process.readProcessWithExitCode a b c) `P.catch` const @_ @IOError (pure Nothing)
392395
getEnvironment = liftIO P.getEnvironment
393396
getCurrentYear = liftIO P.getCurrentYear
394397
listFilesInside test dir = do
@@ -438,6 +441,7 @@ instance Interactive PurePrompt where
438441
readProcessWithExitCode !_ !_ !_ = do
439442
input <- pop
440443
return (ExitSuccess, input, "")
444+
maybeReadProcessWithExitCode a b c = Just <$> readProcessWithExitCode a b c
441445
getEnvironment = fmap (map read) popList
442446
getCurrentYear = fmap read pop
443447
listFilesInside pred' !_ = do
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
# cabal init
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
import Test.Cabal.Prelude
2+
import System.Directory
3+
import System.FilePath
4+
import Distribution.Simple.Utils
5+
import Distribution.Verbosity
6+
7+
-- Test cabal init when git is not installed
8+
main = do
9+
skipIfWindows "Might fail on windows."
10+
tmp <- getTemporaryDirectory
11+
withTempDirectory normal tmp "bin" $
12+
\bin -> cabalTest $
13+
do
14+
ghc_path <- programPathM ghcProgram
15+
cabal_path <- programPathM cabalProgram
16+
withSymlink ghc_path (bin </> "ghc") . withSymlink cabal_path (bin </> "cabal") .
17+
withEnv [("PATH", Just bin)] $ do
18+
cwd <- fmap testSourceCopyDir getTestEnv
19+
20+
void . withDirectory cwd $ do
21+
cabalWithStdin "init" ["-i"]
22+
"2\n\n5\n\n\n2\n\n\n\n\n\n\n\n\n\n"

changelog.d/pr-10486

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
synopsis: Fix a bug that causes `cabal init` to crash if `git` is not installed
2+
packages: cabal-install
3+
prs: #10486
4+
issues: #10484 #8478
5+
significance:
6+
7+
description: {
8+
9+
- `cabal init` tries to use `git config` to guess the user's name and email.
10+
It no longer crashes if there is no executable named `git` on $PATH.
11+
12+
}

0 commit comments

Comments
 (0)