block all commands that don't work in direct mode

I left status working in direct mode, although it doesn't show correct
stats for known annex keys.
This commit is contained in:
Joey Hess 2012-12-29 14:28:19 -04:00
parent 9f2150c7d3
commit 2ce736ac50
24 changed files with 41 additions and 40 deletions

View file

@ -13,6 +13,7 @@ module Checks where
import Common.Annex import Common.Annex
import Types.Command import Types.Command
import Init import Init
import Config
commonChecks :: [CommandCheck] commonChecks :: [CommandCheck]
commonChecks = [repoExists] commonChecks = [repoExists]
@ -20,6 +21,10 @@ commonChecks = [repoExists]
repoExists :: CommandCheck repoExists :: CommandCheck
repoExists = CommandCheck 0 ensureInitialized repoExists = CommandCheck 0 ensureInitialized
notDirect :: Command -> Command
notDirect = addCheck $ whenM isDirect $
error "You cannot run this subcommand in a direct mode repository."
dontCheck :: CommandCheck -> Command -> Command dontCheck :: CommandCheck -> Command -> Command
dontCheck check cmd = mutateCheck cmd $ \c -> filter (/= check) c dontCheck check cmd = mutateCheck cmd $ \c -> filter (/= check) c
@ -29,3 +34,4 @@ addCheck check cmd = mutateCheck cmd $ \c ->
mutateCheck :: Command -> ([CommandCheck] -> [CommandCheck]) -> Command mutateCheck :: Command -> ([CommandCheck] -> [CommandCheck]) -> Command
mutateCheck cmd@(Command { cmdcheck = c }) a = cmd { cmdcheck = a c } mutateCheck cmd@(Command { cmdcheck = c }) a = cmd { cmdcheck = a c }

View file

@ -18,7 +18,6 @@ module Command (
whenAnnexed, whenAnnexed,
ifAnnexed, ifAnnexed,
notBareRepo, notBareRepo,
notDirect,
isBareRepo, isBareRepo,
numCopies, numCopies,
numCopiesCheck, numCopiesCheck,
@ -104,12 +103,6 @@ notBareRepo a = do
error "You cannot run this subcommand in a bare repository." error "You cannot run this subcommand in a bare repository."
a a
notDirect :: Annex a -> Annex a
notDirect a = ifM isDirect
( error "You cannot run this subcommand in a direct mode repository."
, a
)
isBareRepo :: Annex Bool isBareRepo :: Annex Bool
isBareRepo = fromRepo Git.repoIsLocalBare isBareRepo = fromRepo Git.repoIsLocalBare

View file

@ -23,7 +23,7 @@ import Utility.FileMode
import Config import Config
def :: [Command] def :: [Command]
def = [command "add" paramPaths seek "add files to annex"] def = [notDirect $ command "add" paramPaths seek "add files to annex"]
{- Add acts on both files not checked into git yet, and unlocked files. -} {- Add acts on both files not checked into git yet, and unlocked files. -}
seek :: [CommandSeek] seek :: [CommandSeek]
@ -33,7 +33,7 @@ seek = [withFilesNotInGit start, withFilesUnlocked start]
- backend, and then moving it into the annex directory and setting up - backend, and then moving it into the annex directory and setting up
- the symlink pointing to its content. -} - the symlink pointing to its content. -}
start :: FilePath -> CommandStart start :: FilePath -> CommandStart
start file = notBareRepo $ notDirect $ ifAnnexed file fixup add start file = notBareRepo $ ifAnnexed file fixup add
where where
add = do add = do
s <- liftIO $ getSymbolicLinkStatus file s <- liftIO $ getSymbolicLinkStatus file

View file

@ -14,14 +14,16 @@ import qualified Command.Add
import Types.Key import Types.Key
def :: [Command] def :: [Command]
def = [command "addunused" (paramRepeating paramNumRange) def = [notDirect $ command "addunused" (paramRepeating paramNumRange)
seek "add back unused files"] seek "add back unused files"]
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withUnusedMaps start] seek = [withUnusedMaps start]
start :: UnusedMaps -> Int -> CommandStart start :: UnusedMaps -> Int -> CommandStart
start = startUnused "addunused" perform (performOther "bad") (performOther "tmp") start = startUnused "addunused" perform
(performOther "bad")
(performOther "tmp")
perform :: Key -> CommandPerform perform :: Key -> CommandPerform
perform key = next $ Command.Add.cleanup file key True perform key = next $ Command.Add.cleanup file key True

View file

@ -24,7 +24,7 @@ import Types.KeySource
import Config import Config
def :: [Command] def :: [Command]
def = [withOptions [fileOption, pathdepthOption] $ def = [notDirect $ withOptions [fileOption, pathdepthOption] $
command "addurl" (paramRepeating paramUrl) seek "add urls to annex"] command "addurl" (paramRepeating paramUrl) seek "add urls to annex"]
fileOption :: Option fileOption :: Option

View file

@ -14,8 +14,9 @@ import qualified Remote
import Annex.Wanted import Annex.Wanted
def :: [Command] def :: [Command]
def = [withOptions Command.Move.options $ command "copy" paramPaths seek def = [notDirect $
"copy content of files to/from another repository"] withOptions Command.Move.options $ command "copy" paramPaths seek
"copy content of files to/from another repository"]
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withField Command.Move.toOption Remote.byName $ \to -> seek = [withField Command.Move.toOption Remote.byName $ \to ->

View file

@ -20,7 +20,7 @@ import qualified Option
import Annex.Wanted import Annex.Wanted
def :: [Command] def :: [Command]
def = [withOptions [fromOption] $ command "drop" paramPaths seek def = [notDirect $ withOptions [fromOption] $ command "drop" paramPaths seek
"indicate content of files not currently wanted"] "indicate content of files not currently wanted"]
fromOption :: Option fromOption :: Option

View file

@ -20,7 +20,7 @@ import Types.Key
import qualified Option import qualified Option
def :: [Command] def :: [Command]
def = [noCommit $ withOptions [formatOption, print0Option] $ def = [notDirect $ noCommit $ withOptions [formatOption, print0Option] $
command "find" paramPaths seek "lists available files"] command "find" paramPaths seek "lists available files"]
formatOption :: Option formatOption :: Option

View file

@ -13,7 +13,7 @@ import qualified Annex.Queue
import Annex.Content import Annex.Content
def :: [Command] def :: [Command]
def = [noCommit $ command "fix" paramPaths seek def = [notDirect $ noCommit $ command "fix" paramPaths seek
"fix up symlinks to point to annexed content"] "fix up symlinks to point to annexed content"]
seek :: [CommandSeek] seek :: [CommandSeek]

View file

@ -14,7 +14,7 @@ import Annex.Content
import Types.Key import Types.Key
def :: [Command] def :: [Command]
def = [command "fromkey" (paramPair paramKey paramPath) seek def = [notDirect $ command "fromkey" (paramPair paramKey paramPath) seek
"adds a file using a specific key"] "adds a file using a specific key"]
seek :: [CommandSeek] seek :: [CommandSeek]

View file

@ -34,7 +34,7 @@ import System.Posix.Types (EpochTime)
import System.Locale import System.Locale
def :: [Command] def :: [Command]
def = [withOptions options $ command "fsck" paramPaths seek def = [notDirect $ withOptions options $ command "fsck" paramPaths seek
"check for problems"] "check for problems"]
fromOption :: Option fromOption :: Option

View file

@ -13,7 +13,8 @@ import qualified Annex
import qualified Command.Add import qualified Command.Add
def :: [Command] def :: [Command]
def = [command "import" paramPaths seek "move and add files from outside git working copy"] def = [notDirect $ command "import" paramPaths seek
"move and add files from outside git working copy"]
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withPathContents start] seek = [withPathContents start]

View file

@ -12,7 +12,7 @@ import Command
import qualified Annex.Queue import qualified Annex.Queue
def :: [Command] def :: [Command]
def = [command "lock" paramPaths seek "undo unlock command"] def = [notDirect $ command "lock" paramPaths seek "undo unlock command"]
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withFilesUnlocked start, withFilesUnlockedToBeCommitted start] seek = [withFilesUnlocked start, withFilesUnlockedToBeCommitted start]

View file

@ -36,7 +36,7 @@ data RefChange = RefChange
type Outputter = Bool -> POSIXTime -> [UUID] -> Annex () type Outputter = Bool -> POSIXTime -> [UUID] -> Annex ()
def :: [Command] def :: [Command]
def = [withOptions options $ def = [notDirect $ withOptions options $
command "log" paramPaths seek "shows location log"] command "log" paramPaths seek "shows location log"]
options :: [Option] options :: [Option]

View file

@ -18,7 +18,8 @@ import qualified Command.ReKey
import qualified Command.Fsck import qualified Command.Fsck
def :: [Command] def :: [Command]
def = [command "migrate" paramPaths seek "switch data to different backend"] def = [notDirect $
command "migrate" paramPaths seek "switch data to different backend"]
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withFilesInGit $ whenAnnexed start] seek = [withFilesInGit $ whenAnnexed start]

View file

@ -19,7 +19,7 @@ import Logs.Presence
import Logs.Transfer import Logs.Transfer
def :: [Command] def :: [Command]
def = [withOptions options $ command "move" paramPaths seek def = [notDirect $ withOptions options $ command "move" paramPaths seek
"move content of files to/from another repository"] "move content of files to/from another repository"]
fromOption :: Option fromOption :: Option

View file

@ -16,7 +16,7 @@ import qualified Command.Add
import Logs.Web import Logs.Web
def :: [Command] def :: [Command]
def = [command "rekey" def = [notDirect $ command "rekey"
(paramOptional $ paramRepeating $ paramPair paramPath paramKey) (paramOptional $ paramRepeating $ paramPair paramPath paramKey)
seek "change keys used for files"] seek "change keys used for files"]

View file

@ -14,7 +14,7 @@ import Annex.Content
import qualified Command.Fsck import qualified Command.Fsck
def :: [Command] def :: [Command]
def = [command "reinject" (paramPair "SRC" "DEST") seek def = [notDirect $ command "reinject" (paramPair "SRC" "DEST") seek
"sets content of annexed file"] "sets content of annexed file"]
seek :: [CommandSeek] seek :: [CommandSeek]

View file

@ -16,7 +16,8 @@ import qualified Git.Command
import qualified Git.LsFiles as LsFiles import qualified Git.LsFiles as LsFiles
def :: [Command] def :: [Command]
def = [command "unannex" paramPaths seek "undo accidential add command"] def = [notDirect $
command "unannex" paramPaths seek "undo accidential add command"]
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withFilesInGit $ whenAnnexed start] seek = [withFilesInGit $ whenAnnexed start]

View file

@ -18,7 +18,7 @@ import qualified Annex.Branch
import Annex.Content import Annex.Content
def :: [Command] def :: [Command]
def = [addCheck check $ command "uninit" paramPaths seek def = [notDirect $ addCheck check $ command "uninit" paramPaths seek
"de-initialize git-annex and clean out repository"] "de-initialize git-annex and clean out repository"]
check :: Annex () check :: Annex ()

View file

@ -18,7 +18,7 @@ def =
, c "edit" "same as unlock" , c "edit" "same as unlock"
] ]
where where
c n = command n paramPaths seek c n = notDirect . command n paramPaths seek
seek :: [CommandSeek] seek :: [CommandSeek]
seek = [withFilesInGit $ whenAnnexed start] seek = [withFilesInGit $ whenAnnexed start]

View file

@ -15,7 +15,7 @@ import Remote
import Logs.Trust import Logs.Trust
def :: [Command] def :: [Command]
def = [noCommit $ command "whereis" paramPaths seek def = [notDirect $ noCommit $ command "whereis" paramPaths seek
"lists repositories that have file content"] "lists repositories that have file content"]
seek :: [CommandSeek] seek :: [CommandSeek]

4
debian/changelog vendored
View file

@ -3,8 +3,8 @@ git-annex (3.20121212) UNRELEASED; urgency=low
* direct, indirect: New commands, that switch a repository to and from * direct, indirect: New commands, that switch a repository to and from
direct mode. In direct mode, files are accessed directly, rather than direct mode. In direct mode, files are accessed directly, rather than
via symlinks. Note that direct mode is currently experimental. Many via symlinks. Note that direct mode is currently experimental. Many
git and git-annex commands do not work, or can even cause data loss in git-annex commands do not work in direct mode. Some git commands can
direct mode. cause data loss when used in direct mode repositories.
* assistant: Support direct mode. * assistant: Support direct mode.
* OSX assistant: Now uses the FSEvents API to detect file changes. * OSX assistant: Now uses the FSEvents API to detect file changes.
This avoids issues with running out of file descriptors on large trees, This avoids issues with running out of file descriptors on large trees,

View file

@ -42,9 +42,9 @@ changed files to git, pushes them out, pulls down any changes, etc.
You can also run `git annex get` to transfer the content of files into your You can also run `git annex get` to transfer the content of files into your
direct mode repository. Or if the direct mode repository is a remote of direct mode repository. Or if the direct mode repository is a remote of
some other, regular git-annex repository, you can use commands like `git some other, regular git-annex repository, you can use commands in the other
annex copy` and `git annex move` to transfer the contents of files to the repository like `git annex copy` and `git annex move` to transfer the
direct mode repository. contents of files to the direct mode repository.
You can use `git commit --staged`. (But not `git commit -a` .. It'll commit You can use `git commit --staged`. (But not `git commit -a` .. It'll commit
whole large files into git!) whole large files into git!)
@ -53,15 +53,11 @@ You can use `git log` and other git query commands.
## what doesn't work in direct mode ## what doesn't work in direct mode
Don't use `git annex add` -- it thinks all direct mode files are unlocked,
and locks them.
In general git-annex commands will only work in direct mode repositories on In general git-annex commands will only work in direct mode repositories on
files whose content is not present. That's because such files are still files whose content is not present. That's because such files are still
represented as symlinks, which git-annex commands know how to operate on. represented as symlinks, which git-annex commands know how to operate on.
So, `git annex get` works, but `git annex drop` and `git annex move` don't, So, `git annex get` works, but `git annex drop` and `git annex move` don't,
and things like `git annex fsck` and `git annex status` show incomplete and things like `git annex status` show incomplete information.
information.
It's technically possible to make all git-annex commands work in direct It's technically possible to make all git-annex commands work in direct
mode repositories, so this might change. Check back to this page to see mode repositories, so this might change. Check back to this page to see