2010-10-27 17:12:02 +00:00
|
|
|
{- git repository command queue
|
2010-10-27 20:53:54 +00:00
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2010,2012 Joey Hess <id@joeyh.name>
|
2010-10-27 20:53:54 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
2010-10-26 19:59:50 +00:00
|
|
|
-}
|
|
|
|
|
2013-10-17 19:56:56 +00:00
|
|
|
{-# LANGUAGE CPP, BangPatterns #-}
|
2012-02-15 15:13:13 +00:00
|
|
|
|
2011-06-30 17:25:37 +00:00
|
|
|
module Git.Queue (
|
2010-10-26 19:59:50 +00:00
|
|
|
Queue,
|
2011-12-20 18:37:53 +00:00
|
|
|
new,
|
2012-06-07 19:19:44 +00:00
|
|
|
addCommand,
|
|
|
|
addUpdateIndex,
|
2011-03-16 19:10:15 +00:00
|
|
|
size,
|
2011-04-07 17:59:31 +00:00
|
|
|
full,
|
2012-02-15 15:13:13 +00:00
|
|
|
flush,
|
2015-11-05 22:21:48 +00:00
|
|
|
merge,
|
2010-10-26 19:59:50 +00:00
|
|
|
) where
|
|
|
|
|
2012-02-01 20:05:02 +00:00
|
|
|
import Utility.SafeCommand
|
2011-12-20 18:37:53 +00:00
|
|
|
import Common
|
2011-06-30 17:25:37 +00:00
|
|
|
import Git
|
2011-12-14 19:56:11 +00:00
|
|
|
import Git.Command
|
2012-06-07 19:19:44 +00:00
|
|
|
import qualified Git.UpdateIndex
|
2013-10-17 19:56:56 +00:00
|
|
|
|
2014-02-25 18:09:39 +00:00
|
|
|
import qualified Data.Map as M
|
|
|
|
|
2015-11-05 22:21:48 +00:00
|
|
|
{- Queable actions that can be performed in a git repository. -}
|
2012-06-07 19:19:44 +00:00
|
|
|
data Action
|
|
|
|
{- Updating the index file, using a list of streamers that can
|
|
|
|
- be added to as the queue grows. -}
|
2015-11-05 22:21:48 +00:00
|
|
|
= UpdateIndexAction [Git.UpdateIndex.Streamer] -- in reverse order
|
2012-06-07 19:19:44 +00:00
|
|
|
{- A git command to run, on a list of files that can be added to
|
|
|
|
- as the queue grows. -}
|
|
|
|
| CommandAction
|
|
|
|
{ getSubcommand :: String
|
|
|
|
, getParams :: [CommandParam]
|
2013-08-01 19:15:49 +00:00
|
|
|
, getFiles :: [CommandParam]
|
2012-06-07 19:19:44 +00:00
|
|
|
}
|
2010-10-26 19:59:50 +00:00
|
|
|
|
2012-06-07 19:19:44 +00:00
|
|
|
{- A key that can uniquely represent an action in a Map. -}
|
|
|
|
data ActionKey = UpdateIndexActionKey | CommandActionKey String
|
|
|
|
deriving (Eq, Ord)
|
2010-10-26 19:59:50 +00:00
|
|
|
|
2012-06-07 19:19:44 +00:00
|
|
|
actionKey :: Action -> ActionKey
|
|
|
|
actionKey (UpdateIndexAction _) = UpdateIndexActionKey
|
|
|
|
actionKey CommandAction { getSubcommand = s } = CommandActionKey s
|
2012-06-05 00:41:22 +00:00
|
|
|
|
2010-10-26 19:59:50 +00:00
|
|
|
{- A queue of actions to perform (in any order) on a git repository,
|
|
|
|
- with lists of files to perform them on. This allows coalescing
|
|
|
|
- similar git commands. -}
|
2012-02-15 15:13:13 +00:00
|
|
|
data Queue = Queue
|
|
|
|
{ size :: Int
|
|
|
|
, _limit :: Int
|
2012-06-07 19:19:44 +00:00
|
|
|
, items :: M.Map ActionKey Action
|
2012-02-15 15:13:13 +00:00
|
|
|
}
|
2010-10-26 19:59:50 +00:00
|
|
|
|
2011-04-07 17:59:31 +00:00
|
|
|
{- A recommended maximum size for the queue, after which it should be
|
|
|
|
- run.
|
|
|
|
-
|
|
|
|
- 10240 is semi-arbitrary. If we assume git filenames are between 10 and
|
|
|
|
- 255 characters long, then the queue will build up between 100kb and
|
|
|
|
- 2550kb long commands. The max command line length on linux is somewhere
|
|
|
|
- above 20k, so this is a fairly good balance -- the queue will buffer
|
|
|
|
- only a few megabytes of stuff and a minimal number of commands will be
|
|
|
|
- run by xargs. -}
|
2012-02-15 15:13:13 +00:00
|
|
|
defaultLimit :: Int
|
|
|
|
defaultLimit = 10240
|
2011-04-07 17:59:31 +00:00
|
|
|
|
2010-10-26 19:59:50 +00:00
|
|
|
{- Constructor for empty queue. -}
|
2012-02-15 15:13:13 +00:00
|
|
|
new :: Maybe Int -> Queue
|
|
|
|
new lim = Queue 0 (fromMaybe defaultLimit lim) M.empty
|
2010-10-26 19:59:50 +00:00
|
|
|
|
2012-06-07 19:40:44 +00:00
|
|
|
{- Adds an git command to the queue.
|
2012-06-07 19:19:44 +00:00
|
|
|
-
|
2012-06-07 19:40:44 +00:00
|
|
|
- Git commands with the same subcommand but different parameters are
|
|
|
|
- assumed to be equivilant enough to perform in any order with the same
|
|
|
|
- result.
|
2012-06-07 19:19:44 +00:00
|
|
|
-}
|
|
|
|
addCommand :: String -> [CommandParam] -> [FilePath] -> Queue -> Repo -> IO Queue
|
|
|
|
addCommand subcommand params files q repo =
|
2014-06-18 21:23:36 +00:00
|
|
|
updateQueue action different (length files) q repo
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
action = CommandAction
|
|
|
|
{ getSubcommand = subcommand
|
|
|
|
, getParams = params
|
2015-11-05 22:21:48 +00:00
|
|
|
, getFiles = map File files
|
2012-12-13 04:24:19 +00:00
|
|
|
}
|
2014-06-18 21:23:36 +00:00
|
|
|
|
2012-12-13 04:24:19 +00:00
|
|
|
different (CommandAction { getSubcommand = s }) = s /= subcommand
|
|
|
|
different _ = True
|
2012-06-07 19:19:44 +00:00
|
|
|
|
2012-06-10 17:56:04 +00:00
|
|
|
{- Adds an update-index streamer to the queue. -}
|
2012-06-07 19:19:44 +00:00
|
|
|
addUpdateIndex :: Git.UpdateIndex.Streamer -> Queue -> Repo -> IO Queue
|
|
|
|
addUpdateIndex streamer q repo =
|
2012-06-10 17:56:04 +00:00
|
|
|
updateQueue action different 1 q repo
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
-- the list is built in reverse order
|
2015-11-05 22:21:48 +00:00
|
|
|
action = UpdateIndexAction [streamer]
|
2012-06-07 19:19:44 +00:00
|
|
|
|
2012-12-13 04:24:19 +00:00
|
|
|
different (UpdateIndexAction _) = False
|
|
|
|
different _ = True
|
2012-06-07 19:19:44 +00:00
|
|
|
|
|
|
|
{- Updates or adds an action in the queue. If the queue already contains a
|
|
|
|
- different action, it will be flushed; this is to ensure that conflicting
|
|
|
|
- actions, like add and rm, are run in the right order.-}
|
|
|
|
updateQueue :: Action -> (Action -> Bool) -> Int -> Queue -> Repo -> IO Queue
|
2012-06-13 01:13:15 +00:00
|
|
|
updateQueue !action different sizeincrease q repo
|
2012-06-07 19:19:44 +00:00
|
|
|
| null (filter different (M.elems (items q))) = return $ go q
|
|
|
|
| otherwise = go <$> flush q repo
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
go q' = newq
|
|
|
|
where
|
|
|
|
!newq = q'
|
|
|
|
{ size = newsize
|
|
|
|
, items = newitems
|
|
|
|
}
|
|
|
|
!newsize = size q' + sizeincrease
|
2015-11-05 22:21:48 +00:00
|
|
|
!newitems = M.insertWith' combineNewOld (actionKey action) action (items q')
|
|
|
|
|
|
|
|
combineNewOld :: Action -> Action -> Action
|
|
|
|
combineNewOld (CommandAction _sc1 _ps1 fs1) (CommandAction sc2 ps2 fs2) =
|
|
|
|
CommandAction sc2 ps2 (fs1++fs2)
|
|
|
|
combineNewOld (UpdateIndexAction s1) (UpdateIndexAction s2) =
|
|
|
|
UpdateIndexAction (s1++s2)
|
|
|
|
combineNewOld anew _aold = anew
|
|
|
|
|
|
|
|
{- Merges the contents of the second queue into the first.
|
|
|
|
- This should only be used when the two queues are known to contain
|
|
|
|
- non-conflicting actions. -}
|
|
|
|
merge :: Queue -> Queue -> Queue
|
|
|
|
merge origq newq = origq
|
|
|
|
{ size = size origq + size newq
|
|
|
|
, items = M.unionWith combineNewOld (items newq) (items origq)
|
|
|
|
}
|
2010-10-26 19:59:50 +00:00
|
|
|
|
2011-04-07 17:59:31 +00:00
|
|
|
{- Is a queue large enough that it should be flushed? -}
|
|
|
|
full :: Queue -> Bool
|
2016-01-13 18:55:01 +00:00
|
|
|
full (Queue cur lim _) = cur >= lim
|
2011-04-07 17:59:31 +00:00
|
|
|
|
2010-10-26 19:59:50 +00:00
|
|
|
{- Runs a queue on a git repository. -}
|
2011-11-08 19:34:10 +00:00
|
|
|
flush :: Queue -> Repo -> IO Queue
|
2012-02-15 15:13:13 +00:00
|
|
|
flush (Queue _ lim m) repo = do
|
2012-06-07 19:19:44 +00:00
|
|
|
forM_ (M.elems m) $ runAction repo
|
2012-02-15 15:13:13 +00:00
|
|
|
return $ Queue 0 lim M.empty
|
2010-10-26 19:59:50 +00:00
|
|
|
|
|
|
|
{- Runs an Action on a list of files in a git repository.
|
|
|
|
-
|
2011-07-14 20:56:06 +00:00
|
|
|
- Complicated by commandline length limits.
|
|
|
|
-
|
|
|
|
- Intentionally runs the command even if the list of files is empty;
|
|
|
|
- this allows queueing commands that do not need a list of files. -}
|
2012-06-07 19:19:44 +00:00
|
|
|
runAction :: Repo -> Action -> IO ()
|
2012-06-07 19:40:44 +00:00
|
|
|
runAction repo (UpdateIndexAction streamers) =
|
2012-06-13 01:13:15 +00:00
|
|
|
-- list is stored in reverse order
|
|
|
|
Git.UpdateIndex.streamUpdateIndex repo $ reverse streamers
|
2014-02-25 18:53:43 +00:00
|
|
|
runAction repo action@(CommandAction {}) = do
|
2013-10-17 19:56:56 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2014-02-25 18:09:39 +00:00
|
|
|
let p = (proc "xargs" $ "-0":"git":toCommand gitparams) { env = gitEnv repo }
|
2012-08-25 00:50:39 +00:00
|
|
|
withHandle StdinHandle createProcessSuccess p $ \h -> do
|
2012-07-19 04:43:36 +00:00
|
|
|
fileEncoding h
|
2013-08-01 19:15:49 +00:00
|
|
|
hPutStr h $ intercalate "\0" $ toCommand $ getFiles action
|
2012-07-19 04:43:36 +00:00
|
|
|
hClose h
|
2013-10-17 19:56:56 +00:00
|
|
|
#else
|
|
|
|
-- Using xargs on Windows is problimatic, so just run the command
|
|
|
|
-- once per file (not as efficient.)
|
|
|
|
if null (getFiles action)
|
2014-06-12 22:37:12 +00:00
|
|
|
then void $ boolSystemEnv "git" gitparams (gitEnv repo)
|
2013-10-17 19:56:56 +00:00
|
|
|
else forM_ (getFiles action) $ \f ->
|
2014-06-12 22:37:12 +00:00
|
|
|
void $ boolSystemEnv "git" (gitparams ++ [f]) (gitEnv repo)
|
2013-10-17 19:56:56 +00:00
|
|
|
#endif
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
2013-10-17 19:56:56 +00:00
|
|
|
gitparams = gitCommandLine
|
2012-12-13 04:24:19 +00:00
|
|
|
(Param (getSubcommand action):getParams action) repo
|