40ecf58d4b
This does not change the overall license of the git-annex program, which was already AGPL due to a number of sources files being AGPL already. Legally speaking, I'm adding a new license under which these files are now available; I already released their current contents under the GPL license. Now they're dual licensed GPL and AGPL. However, I intend for all my future changes to these files to only be released under the AGPL license, and I won't be tracking the dual licensing status, so I'm simply changing the license statement to say it's AGPL. (In some cases, others wrote parts of the code of a file and released it under the GPL; but in all cases I have contributed a significant portion of the code in each file and it's that code that is getting the AGPL license; the GPL license of other contributors allows combining with AGPL code.)
146 lines
4.1 KiB
Haskell
146 lines
4.1 KiB
Haskell
{- git-update-index library
|
|
-
|
|
- Copyright 2011-2018 Joey Hess <id@joeyh.name>
|
|
-
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
-}
|
|
|
|
{-# LANGUAGE BangPatterns, CPP #-}
|
|
|
|
module Git.UpdateIndex (
|
|
Streamer,
|
|
pureStreamer,
|
|
streamUpdateIndex,
|
|
streamUpdateIndex',
|
|
startUpdateIndex,
|
|
stopUpdateIndex,
|
|
lsTree,
|
|
lsSubTree,
|
|
updateIndexLine,
|
|
stageFile,
|
|
unstageFile,
|
|
stageSymlink,
|
|
stageDiffTreeItem,
|
|
refreshIndex,
|
|
) where
|
|
|
|
import Common
|
|
import Git
|
|
import Git.Types
|
|
import Git.Command
|
|
import Git.FilePath
|
|
import Git.Sha
|
|
import qualified Git.DiffTreeItem as Diff
|
|
|
|
{- Streamers are passed a callback and should feed it lines in the form
|
|
- read by update-index, and generated by ls-tree. -}
|
|
type Streamer = (String -> IO ()) -> IO ()
|
|
|
|
{- A streamer with a precalculated value. -}
|
|
pureStreamer :: String -> Streamer
|
|
pureStreamer !s = \streamer -> streamer s
|
|
|
|
{- Streams content into update-index from a list of Streamers. -}
|
|
streamUpdateIndex :: Repo -> [Streamer] -> IO ()
|
|
streamUpdateIndex repo as = bracket (startUpdateIndex repo) stopUpdateIndex $
|
|
(\h -> forM_ as $ streamUpdateIndex' h)
|
|
|
|
data UpdateIndexHandle = UpdateIndexHandle ProcessHandle Handle
|
|
|
|
streamUpdateIndex' :: UpdateIndexHandle -> Streamer -> IO ()
|
|
streamUpdateIndex' (UpdateIndexHandle _ h) a = a $ \s -> do
|
|
hPutStr h s
|
|
hPutStr h "\0"
|
|
|
|
startUpdateIndex :: Repo -> IO UpdateIndexHandle
|
|
startUpdateIndex repo = do
|
|
(Just h, _, _, p) <- createProcess (gitCreateProcess params repo)
|
|
{ std_in = CreatePipe }
|
|
return $ UpdateIndexHandle p h
|
|
where
|
|
params = map Param ["update-index", "-z", "--index-info"]
|
|
|
|
stopUpdateIndex :: UpdateIndexHandle -> IO Bool
|
|
stopUpdateIndex (UpdateIndexHandle p h) = do
|
|
hClose h
|
|
checkSuccessProcess p
|
|
|
|
{- A streamer that adds the current tree for a ref. Useful for eg, copying
|
|
- and modifying branches. -}
|
|
lsTree :: Ref -> Repo -> Streamer
|
|
lsTree (Ref x) repo streamer = do
|
|
(s, cleanup) <- pipeNullSplit params repo
|
|
mapM_ streamer s
|
|
void $ cleanup
|
|
where
|
|
params = map Param ["ls-tree", "-z", "-r", "--full-tree", x]
|
|
lsSubTree :: Ref -> FilePath -> Repo -> Streamer
|
|
lsSubTree (Ref x) p repo streamer = do
|
|
(s, cleanup) <- pipeNullSplit params repo
|
|
mapM_ streamer s
|
|
void $ cleanup
|
|
where
|
|
params = map Param ["ls-tree", "-z", "-r", "--full-tree", x, p]
|
|
|
|
{- Generates a line suitable to be fed into update-index, to add
|
|
- a given file with a given sha. -}
|
|
updateIndexLine :: Sha -> TreeItemType -> TopFilePath -> String
|
|
updateIndexLine sha treeitemtype file = concat
|
|
[ fmtTreeItemType treeitemtype
|
|
, " blob "
|
|
, fromRef sha
|
|
, "\t"
|
|
, indexPath file
|
|
]
|
|
|
|
stageFile :: Sha -> TreeItemType -> FilePath -> Repo -> IO Streamer
|
|
stageFile sha treeitemtype file repo = do
|
|
p <- toTopFilePath file repo
|
|
return $ pureStreamer $ updateIndexLine sha treeitemtype p
|
|
|
|
{- A streamer that removes a file from the index. -}
|
|
unstageFile :: FilePath -> Repo -> IO Streamer
|
|
unstageFile file repo = do
|
|
p <- toTopFilePath file repo
|
|
return $ unstageFile' p
|
|
|
|
unstageFile' :: TopFilePath -> Streamer
|
|
unstageFile' p = pureStreamer $ "0 " ++ fromRef nullSha ++ "\t" ++ indexPath p
|
|
|
|
{- A streamer that adds a symlink to the index. -}
|
|
stageSymlink :: FilePath -> Sha -> Repo -> IO Streamer
|
|
stageSymlink file sha repo = do
|
|
!line <- updateIndexLine
|
|
<$> pure sha
|
|
<*> pure TreeSymlink
|
|
<*> toTopFilePath file repo
|
|
return $ pureStreamer line
|
|
|
|
{- A streamer that applies a DiffTreeItem to the index. -}
|
|
stageDiffTreeItem :: Diff.DiffTreeItem -> Streamer
|
|
stageDiffTreeItem d = case toTreeItemType (Diff.dstmode d) of
|
|
Nothing -> unstageFile' (Diff.file d)
|
|
Just t -> pureStreamer $ updateIndexLine (Diff.dstsha d) t (Diff.file d)
|
|
|
|
indexPath :: TopFilePath -> InternalGitPath
|
|
indexPath = toInternalGitPath . getTopFilePath
|
|
|
|
{- Refreshes the index, by checking file stat information. -}
|
|
refreshIndex :: Repo -> ((FilePath -> IO ()) -> IO ()) -> IO Bool
|
|
refreshIndex repo feeder = do
|
|
(Just h, _, _, p) <- createProcess (gitCreateProcess params repo)
|
|
{ std_in = CreatePipe }
|
|
feeder $ \f -> do
|
|
hPutStr h f
|
|
hPutStr h "\0"
|
|
hFlush h
|
|
hClose h
|
|
checkSuccessProcess p
|
|
where
|
|
params =
|
|
[ Param "update-index"
|
|
, Param "-q"
|
|
, Param "--refresh"
|
|
, Param "-z"
|
|
, Param "--stdin"
|
|
]
|