improve bare repo handing

Many more commands can work in bare repos now, thanks to the git-annex
branch.
This commit is contained in:
Joey Hess 2011-06-22 18:32:41 -04:00
parent 944c51ba26
commit 80302d0b46
11 changed files with 23 additions and 31 deletions

View file

@ -20,7 +20,7 @@ seek :: [CommandSeek]
seek = [withWords start] seek = [withWords start]
start :: CommandStartWords start :: CommandStartWords
start ws = notBareRepo $ do start ws = do
let (name, description) = let (name, description) =
case ws of case ws of
(n:d) -> (n,unwords d) (n:d) -> (n,unwords d)

View file

@ -64,11 +64,11 @@ verifyLocationLog key file = do
case (present, u `elem` uuids) of case (present, u `elem` uuids) of
(True, False) -> do (True, False) -> do
fix u ValuePresent fix g u ValuePresent
-- There is no data loss, so do not fail. -- There is no data loss, so do not fail.
return True return True
(False, True) -> do (False, True) -> do
fix u ValueMissing fix g u ValueMissing
warning $ warning $
"** Based on the location log, " ++ file "** Based on the location log, " ++ file
++ "\n** was expected to be present, " ++ ++ "\n** was expected to be present, " ++
@ -77,6 +77,6 @@ verifyLocationLog key file = do
_ -> return True _ -> return True
where where
fix u s = do fix g u s = do
showNote "fixing location log" showNote "fixing location log"
logStatusFor u key s logChange g key u s

View file

@ -8,7 +8,7 @@
module Command.Init where module Command.Init where
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Control.Monad (when) import Control.Monad (when, unless)
import System.Directory import System.Directory
import Command import Command
@ -44,7 +44,8 @@ perform description = do
u <- getUUID g u <- getUUID g
setVersion setVersion
describeUUID u description describeUUID u description
gitPreCommitHookWrite g unless (Git.repoIsLocalBare g) $
gitPreCommitHookWrite g
next $ return True next $ return True
{- set up a git pre-commit hook, if one is not already present -} {- set up a git pre-commit hook, if one is not already present -}

View file

@ -30,7 +30,7 @@ seek :: [CommandSeek]
seek = [withWords start] seek = [withWords start]
start :: CommandStartWords start :: CommandStartWords
start ws = notBareRepo $ do start ws = do
when (null ws) $ needname when (null ws) $ needname
(u, c) <- findByName name (u, c) <- findByName name

View file

@ -51,12 +51,12 @@ showAction False file = showStart "copy" file
{- Used to log a change in a remote's having a key. The change is logged {- Used to log a change in a remote's having a key. The change is logged
- in the local repo, not on the remote. The process of transferring the - in the local repo, not on the remote. The process of transferring the
- key to the remote, or removing the key from it *may* log the change - key to the remote, or removing the key from it *may* log the change
- on the remote, but this cannot be relied on. For example, it's not done - on the remote, but this cannot be relied on. -}
- for bare repos. -}
remoteHasKey :: Remote.Remote Annex -> Key -> Bool -> Annex () remoteHasKey :: Remote.Remote Annex -> Key -> Bool -> Annex ()
remoteHasKey remote key present = do remoteHasKey remote key present = do
let remoteuuid = Remote.uuid remote let remoteuuid = Remote.uuid remote
logStatusFor remoteuuid key status g <- Annex.gitRepo
logChange g key remoteuuid status
where where
status = if present then ValuePresent else ValueMissing status = if present then ValuePresent else ValueMissing

View file

@ -21,7 +21,7 @@ seek :: [CommandSeek]
seek = [withWords start] seek = [withWords start]
start :: CommandStartWords start :: CommandStartWords
start ws = notBareRepo $ do start ws = do
let name = unwords ws let name = unwords ws
showStart "semitrust" name showStart "semitrust" name
u <- Remote.nameToUUID name u <- Remote.nameToUUID name

View file

@ -21,7 +21,7 @@ seek :: [CommandSeek]
seek = [withWords start] seek = [withWords start]
start :: CommandStartWords start :: CommandStartWords
start ws = notBareRepo $ do start ws = do
let name = unwords ws let name = unwords ws
showStart "trust" name showStart "trust" name
u <- Remote.nameToUUID name u <- Remote.nameToUUID name

View file

@ -21,7 +21,7 @@ seek :: [CommandSeek]
seek = [withWords start] seek = [withWords start]
start :: CommandStartWords start :: CommandStartWords
start ws = notBareRepo $ do start ws = do
let name = unwords ws let name = unwords ws
showStart "untrust" name showStart "untrust" name
u <- Remote.nameToUUID name u <- Remote.nameToUUID name

View file

@ -9,7 +9,6 @@ module Content (
inAnnex, inAnnex,
calcGitLink, calcGitLink,
logStatus, logStatus,
logStatusFor,
getViaTmp, getViaTmp,
getViaTmpUnchecked, getViaTmpUnchecked,
withTmp, withTmp,
@ -27,7 +26,7 @@ import System.IO.Error (try)
import System.Directory import System.Directory
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import System.Path import System.Path
import Control.Monad (when, unless, filterM) import Control.Monad (when, filterM)
import System.Posix.Files import System.Posix.Files
import System.FilePath import System.FilePath
import Data.Maybe import Data.Maybe
@ -71,16 +70,9 @@ calcGitLink file key = do
- updated instead. -} - updated instead. -}
logStatus :: Key -> LogStatus -> Annex () logStatus :: Key -> LogStatus -> Annex ()
logStatus key status = do logStatus key status = do
u <- getUUID =<< Annex.gitRepo
logStatusFor u key status
{- Updates the LocationLog when a key's presence changes in a repository
- identified by UUID. -}
logStatusFor :: UUID -> Key -> LogStatus -> Annex ()
logStatusFor u key status = do
g <- Annex.gitRepo g <- Annex.gitRepo
unless (Git.repoIsLocalBare g) $ do u <- getUUID g
logChange g key u status logChange g key u status
{- Runs an action, passing it a temporary filename to download, {- Runs an action, passing it a temporary filename to download,
- and if the action succeeds, moves the temp file into - and if the action succeeds, moves the temp file into

2
debian/changelog vendored
View file

@ -2,6 +2,8 @@ git-annex (0.20110611) UNRELEASED; urgency=low
* New repository format, annex.version=3. Use `git annex upgrade` to migrate. * New repository format, annex.version=3. Use `git annex upgrade` to migrate.
* Improved handling of bare git repos with annexes. Many more commands will
work in them.
* rsync is now used when copying files from repos on other filesystems. * rsync is now used when copying files from repos on other filesystems.
cp is still used when copying file from repos on the same filesystem, cp is still used when copying file from repos on the same filesystem,
since --reflink=auto can make it significantly faster on filesystems since --reflink=auto can make it significantly faster on filesystems

View file

@ -14,12 +14,9 @@ Known to work ok:
* `git annex drop` can check that a bare repository has a copy of data * `git annex drop` can check that a bare repository has a copy of data
that is being dropped. that is being dropped.
* `git annex get` can transfer data from a bare repository. * `git annex get` can transfer data from a bare repository.
* Most other stuff (ie, init, describe, trust, etc.)
There are a few caveats to keep in mind when using bare repositories: There are a few caveats to keep in mind when using bare repositories:
* Some subcommands, like `fsck`, `trust`, `unused` and `fromkey`, * A few subcommands, like `unused` cannot be run in a bare repository.
cannot be run in a bare repository. Those subcommands will Those subcommands will refuse to do anything.
refuse to do anything.
* `git annex setkey` is a plumbing-level command; using it manually
to add content to a bare repository is not recommended, since there
will be no record that the content is stored there.