git-annex/Git/Command.hs

142 lines
5.1 KiB
Haskell
Raw Normal View History

2011-12-14 19:56:11 +00:00
{- running git commands
-
- Copyright 2010-2013 Joey Hess <id@joeyh.name>
2011-12-14 19:56:11 +00:00
-
- Licensed under the GNU AGPL version 3 or higher.
2011-12-14 19:56:11 +00:00
-}
{-# LANGUAGE CPP #-}
2011-12-14 19:56:11 +00:00
module Git.Command where
import Common
import Git
import Git.Types
2012-09-15 21:25:05 +00:00
import qualified Utility.CoProcess as CoProcess
2011-12-14 19:56:11 +00:00
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString as S
2011-12-14 19:56:11 +00:00
{- Constructs a git command line operating on the specified repo. -}
gitCommandLine :: [CommandParam] -> Repo -> [CommandParam]
gitCommandLine params r@(Repo { location = l@(Local { } ) }) =
setdir ++ settree ++ gitGlobalOpts r ++ params
2012-12-13 04:24:19 +00:00
where
setdir
| gitEnvOverridesGitDir r = []
| otherwise = [Param $ "--git-dir=" ++ fromRawFilePath (gitdir l)]
2012-12-13 04:24:19 +00:00
settree = case worktree l of
Nothing -> []
Just t -> [Param $ "--work-tree=" ++ fromRawFilePath t]
2011-12-14 19:56:11 +00:00
gitCommandLine _ repo = assertLocal repo $ error "internal"
{- Runs git in the specified repo. -}
runBool :: [CommandParam] -> Repo -> IO Bool
runBool params repo = assertLocal repo $
boolSystemEnv "git" (gitCommandLine params repo) (gitEnv repo)
2011-12-14 19:56:11 +00:00
{- Runs git in the specified repo, throwing an error if it fails. -}
run :: [CommandParam] -> Repo -> IO ()
run params repo = assertLocal repo $
unlessM (runBool params repo) $
error $ "git " ++ show params ++ " failed"
2011-12-14 19:56:11 +00:00
{- Runs git and forces it to be quiet, throwing an error if it fails. -}
runQuiet :: [CommandParam] -> Repo -> IO ()
runQuiet params repo = withQuietOutput createProcessSuccess $
(proc "git" $ toCommand $ gitCommandLine (params) repo)
{ env = gitEnv repo }
{- Runs a git command and returns its output, lazily.
2011-12-14 19:56:11 +00:00
-
- Also returns an action that should be used when the output is all
- read, that will wait on the command, and
- return True if it succeeded. Failure to wait will result in zombies.
2011-12-14 19:56:11 +00:00
-}
pipeReadLazy :: [CommandParam] -> Repo -> IO (L.ByteString, IO Bool)
pipeReadLazy params repo = assertLocal repo $ do
2012-10-04 23:41:58 +00:00
(_, Just h, _, pid) <- createProcess p { std_out = CreatePipe }
c <- L.hGetContents h
return (c, checkSuccessProcess pid)
2012-12-13 04:24:19 +00:00
where
p = gitCreateProcess params repo
{- Runs a git command, and returns its output, strictly.
-
- Nonzero exit status is ignored.
-}
pipeReadStrict :: [CommandParam] -> Repo -> IO S.ByteString
pipeReadStrict = pipeReadStrict' S.hGetContents
{- The reader action must be strict. -}
pipeReadStrict' :: (Handle -> IO a) -> [CommandParam] -> Repo -> IO a
pipeReadStrict' reader params repo = assertLocal repo $
withHandle StdoutHandle (createProcessChecked ignoreFailureProcess) p $ \h -> do
output <- reader h
hClose h
return output
2012-12-13 04:24:19 +00:00
where
p = gitCreateProcess params repo
2011-12-14 19:56:11 +00:00
2013-10-20 21:50:51 +00:00
{- Runs a git command, feeding it an input, and returning its output,
2012-07-17 18:40:05 +00:00
- which is expected to be fairly small, since it's all read into memory
- strictly. -}
2013-10-20 21:50:51 +00:00
pipeWriteRead :: [CommandParam] -> Maybe (Handle -> IO ()) -> Repo -> IO String
pipeWriteRead params writer repo = assertLocal repo $
2012-08-25 00:50:39 +00:00
writeReadProcessEnv "git" (toCommand $ gitCommandLine params repo)
2013-10-20 21:50:51 +00:00
(gitEnv repo) writer (Just adjusthandle)
where
adjusthandle h = hSetNewlineMode h noNewlineTranslation
2012-08-25 00:50:39 +00:00
{- Runs a git command, feeding it input on a handle with an action. -}
2012-08-25 00:50:39 +00:00
pipeWrite :: [CommandParam] -> Repo -> (Handle -> IO ()) -> IO ()
pipeWrite params repo = assertLocal repo $
withHandle StdinHandle createProcessSuccess $
gitCreateProcess params repo
2011-12-14 19:56:11 +00:00
{- Reads null terminated output of a git command (as enabled by the -z
- parameter), and splits it. -}
pipeNullSplit :: [CommandParam] -> Repo -> IO ([L.ByteString], IO Bool)
pipeNullSplit params repo = do
(s, cleanup) <- pipeReadLazy params repo
return (filter (not . L.null) $ L.split 0 s, cleanup)
2011-12-14 19:56:11 +00:00
{- Reads lazily, but copies each part to a strict ByteString for
- convenience.
-}
pipeNullSplit' :: [CommandParam] -> Repo -> IO ([S.ByteString], IO Bool)
pipeNullSplit' params repo = do
(s, cleanup) <- pipeNullSplit params repo
return (map L.toStrict s, cleanup)
pipeNullSplitStrict :: [CommandParam] -> Repo -> IO [S.ByteString]
pipeNullSplitStrict params repo = do
s <- pipeReadStrict params repo
return $ filter (not . S.null) $ S.split 0 s
pipeNullSplitZombie :: [CommandParam] -> Repo -> IO [L.ByteString]
pipeNullSplitZombie params repo = leaveZombie <$> pipeNullSplit params repo
pipeNullSplitZombie' :: [CommandParam] -> Repo -> IO [S.ByteString]
pipeNullSplitZombie' params repo = leaveZombie <$> pipeNullSplit' params repo
{- Doesn't run the cleanup action. A zombie results. -}
leaveZombie :: (a, IO Bool) -> a
leaveZombie = fst
2012-09-15 21:25:05 +00:00
{- Runs a git command as a coprocess. -}
gitCoProcessStart :: Bool -> [CommandParam] -> Repo -> IO CoProcess.CoProcessHandle
gitCoProcessStart restartable params repo = CoProcess.start numrestarts "git"
(toCommand $ gitCommandLine params repo)
(gitEnv repo)
where
{- If a long-running git command like cat-file --batch
- crashes, it will likely start up again ok. If it keeps crashing
- 10 times, something is badly wrong. -}
numrestarts = if restartable then 10 else 0
gitCreateProcess :: [CommandParam] -> Repo -> CreateProcess
gitCreateProcess params repo =
(proc "git" $ toCommand $ gitCommandLine params repo)
{ env = gitEnv repo }