2012-12-13 19:44:56 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Command.Indirect where
|
|
|
|
|
|
|
|
import Common.Annex
|
|
|
|
import Command
|
|
|
|
import qualified Git
|
|
|
|
import qualified Git.Command
|
|
|
|
import qualified Git.LsFiles
|
|
|
|
import Config
|
fully support core.symlinks=false in all relevant symlink handling code
Refactored annex link code into nice clean new library.
Audited and dealt with calls to createSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ createSymbolicLink linktarget file
only when core.symlinks=true
Assistant/WebApp/Configurators/Local.hs: createSymbolicLink link link
test if symlinks can be made
Command/Fix.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/FromKey.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/Indirect.hs: liftIO $ createSymbolicLink l f
refuses to run if core.symlinks=false
Init.hs: createSymbolicLink f f2
test if symlinks can be made
Remote/Directory.hs: go [file] = catchBoolIO $ createSymbolicLink file f >> return True
fast key linking; catches failure to make symlink and falls back to copy
Remote/Git.hs: liftIO $ catchBoolIO $ createSymbolicLink loc file >> return True
ditto
Upgrade/V1.hs: liftIO $ createSymbolicLink link f
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to readSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ catchMaybeIO $ readSymbolicLink file
only when core.symlinks=true
Assistant/Threads/Watcher.hs: ifM ((==) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file))
code that fixes real symlinks when inotify sees them
It's ok to not fix psdueo-symlinks.
Assistant/Threads/Watcher.hs: mlink <- liftIO (catchMaybeIO $ readSymbolicLink file)
ditto
Command/Fix.hs: stopUnless ((/=) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file)) $ do
command only works in indirect mode
Upgrade/V1.hs: getsymlink = takeFileName <$> readSymbolicLink file
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to isSymbolicLink.
(Typically used with getSymbolicLinkStatus, but that is just used because
getFileStatus is not as robust; it also works on pseudolinks.)
Remaining calls are all safe, because:
Assistant/Threads/SanityChecker.hs: | isSymbolicLink s -> addsymlink file ms
only handles staging of symlinks that were somehow not staged
(might need to be updated to support pseudolinks, but this is
only a belt-and-suspenders check anyway, and I've never seen the code run)
Command/Add.hs: if isSymbolicLink s || not (isRegularFile s)
avoids adding symlinks to the annex, so not relevant
Command/Indirect.hs: | isSymbolicLink s -> void $ flip whenAnnexed f $
only allowed on systems that support symlinks
Command/Indirect.hs: whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
ditto
Seek.hs:notSymlink f = liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f
used to find unlocked files, only relevant in indirect mode
Utility/FSEvents.hs: | Files.isSymbolicLink s = runhook addSymlinkHook $ Just s
Utility/FSEvents.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: checkfiletype Files.isSymbolicLink addSymlinkHook f
Utility/Kqueue.hs: | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
all above are lower-level, not relevant
Audited and dealt with calls to isSymLink.
Remaining calls are all safe, because:
Annex/Direct.hs: | isSymLink (getmode item) =
This is looking at git diff-tree objects, not files on disk
Command/Unused.hs: | isSymLink (LsTree.mode l) = do
This is looking at git ls-tree, not file on disk
Utility/FileMode.hs:isSymLink :: FileMode -> Bool
Utility/FileMode.hs:isSymLink = checkMode symbolicLinkMode
low-level
Done!!
2013-02-17 19:05:55 +00:00
|
|
|
import qualified Annex
|
2012-12-13 19:44:56 +00:00
|
|
|
import Annex.Direct
|
|
|
|
import Annex.Content
|
|
|
|
import Annex.CatFile
|
2013-02-26 19:13:10 +00:00
|
|
|
import Annex.Version
|
2013-02-15 18:17:31 +00:00
|
|
|
import Init
|
2012-12-13 19:44:56 +00:00
|
|
|
|
|
|
|
def :: [Command]
|
2012-12-29 18:45:19 +00:00
|
|
|
def = [notBareRepo $ command "indirect" paramNothing seek
|
|
|
|
"switch repository to indirect mode"]
|
2012-12-13 19:44:56 +00:00
|
|
|
|
|
|
|
seek :: [CommandSeek]
|
|
|
|
seek = [withNothing start]
|
|
|
|
|
|
|
|
start :: CommandStart
|
2013-02-15 18:17:31 +00:00
|
|
|
start = ifM isDirect
|
fully support core.symlinks=false in all relevant symlink handling code
Refactored annex link code into nice clean new library.
Audited and dealt with calls to createSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ createSymbolicLink linktarget file
only when core.symlinks=true
Assistant/WebApp/Configurators/Local.hs: createSymbolicLink link link
test if symlinks can be made
Command/Fix.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/FromKey.hs: liftIO $ createSymbolicLink link file
command only works in indirect mode
Command/Indirect.hs: liftIO $ createSymbolicLink l f
refuses to run if core.symlinks=false
Init.hs: createSymbolicLink f f2
test if symlinks can be made
Remote/Directory.hs: go [file] = catchBoolIO $ createSymbolicLink file f >> return True
fast key linking; catches failure to make symlink and falls back to copy
Remote/Git.hs: liftIO $ catchBoolIO $ createSymbolicLink loc file >> return True
ditto
Upgrade/V1.hs: liftIO $ createSymbolicLink link f
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to readSymbolicLink.
Remaining calls are all safe, because:
Annex/Link.hs: ( liftIO $ catchMaybeIO $ readSymbolicLink file
only when core.symlinks=true
Assistant/Threads/Watcher.hs: ifM ((==) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file))
code that fixes real symlinks when inotify sees them
It's ok to not fix psdueo-symlinks.
Assistant/Threads/Watcher.hs: mlink <- liftIO (catchMaybeIO $ readSymbolicLink file)
ditto
Command/Fix.hs: stopUnless ((/=) (Just link) <$> liftIO (catchMaybeIO $ readSymbolicLink file)) $ do
command only works in indirect mode
Upgrade/V1.hs: getsymlink = takeFileName <$> readSymbolicLink file
v1 repos could not be on a filesystem w/o symlinks
Audited and dealt with calls to isSymbolicLink.
(Typically used with getSymbolicLinkStatus, but that is just used because
getFileStatus is not as robust; it also works on pseudolinks.)
Remaining calls are all safe, because:
Assistant/Threads/SanityChecker.hs: | isSymbolicLink s -> addsymlink file ms
only handles staging of symlinks that were somehow not staged
(might need to be updated to support pseudolinks, but this is
only a belt-and-suspenders check anyway, and I've never seen the code run)
Command/Add.hs: if isSymbolicLink s || not (isRegularFile s)
avoids adding symlinks to the annex, so not relevant
Command/Indirect.hs: | isSymbolicLink s -> void $ flip whenAnnexed f $
only allowed on systems that support symlinks
Command/Indirect.hs: whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
ditto
Seek.hs:notSymlink f = liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f
used to find unlocked files, only relevant in indirect mode
Utility/FSEvents.hs: | Files.isSymbolicLink s = runhook addSymlinkHook $ Just s
Utility/FSEvents.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: | Files.isSymbolicLink s ->
Utility/INotify.hs: checkfiletype Files.isSymbolicLink addSymlinkHook f
Utility/Kqueue.hs: | Files.isSymbolicLink s = callhook addSymlinkHook (Just s) change
all above are lower-level, not relevant
Audited and dealt with calls to isSymLink.
Remaining calls are all safe, because:
Annex/Direct.hs: | isSymLink (getmode item) =
This is looking at git diff-tree objects, not files on disk
Command/Unused.hs: | isSymLink (LsTree.mode l) = do
This is looking at git ls-tree, not file on disk
Utility/FileMode.hs:isSymLink :: FileMode -> Bool
Utility/FileMode.hs:isSymLink = checkMode symbolicLinkMode
low-level
Done!!
2013-02-17 19:05:55 +00:00
|
|
|
( do
|
|
|
|
unlessM (coreSymlinks <$> Annex.getGitConfig) $
|
|
|
|
error "Git is configured to not use symlinks, so you must use direct mode."
|
|
|
|
whenM probeCrippledFileSystem $
|
|
|
|
error "This repository seems to be on a crippled filesystem, you must use direct mode."
|
|
|
|
next perform
|
2013-02-15 18:17:31 +00:00
|
|
|
, stop
|
|
|
|
)
|
2012-12-13 19:44:56 +00:00
|
|
|
|
|
|
|
perform :: CommandPerform
|
|
|
|
perform = do
|
|
|
|
showStart "commit" ""
|
|
|
|
whenM (stageDirect) $ do
|
|
|
|
showOutput
|
|
|
|
void $ inRepo $ Git.Command.runBool "commit"
|
|
|
|
[Param "-m", Param "commit before switching to indirect mode"]
|
2012-12-13 20:00:17 +00:00
|
|
|
showEndOk
|
2012-12-13 19:44:56 +00:00
|
|
|
|
|
|
|
-- Note that we set indirect mode early, so that we can use
|
|
|
|
-- moveAnnex in indirect mode.
|
|
|
|
setDirect False
|
|
|
|
|
|
|
|
top <- fromRepo Git.repoPath
|
|
|
|
(l, clean) <- inRepo $ Git.LsFiles.stagedDetails [top]
|
|
|
|
forM_ l go
|
|
|
|
void $ liftIO clean
|
|
|
|
next cleanup
|
|
|
|
where
|
|
|
|
{- Walk tree from top and move all present direct mode files into
|
|
|
|
- the annex, replacing with symlinks. Also delete direct mode
|
|
|
|
- caches and mappings. -}
|
|
|
|
go (_, Nothing) = noop
|
|
|
|
go (f, Just sha) = do
|
|
|
|
r <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus f
|
|
|
|
case r of
|
|
|
|
Just s
|
|
|
|
| isSymbolicLink s -> void $ flip whenAnnexed f $
|
|
|
|
\_ (k, _) -> do
|
|
|
|
cleandirect k
|
|
|
|
return Nothing
|
|
|
|
| otherwise ->
|
|
|
|
maybe noop (fromdirect f)
|
|
|
|
=<< catKey sha
|
|
|
|
_ -> noop
|
|
|
|
|
|
|
|
fromdirect f k = do
|
|
|
|
showStart "indirect" f
|
|
|
|
cleandirect k -- clean before content directory gets frozen
|
|
|
|
whenM (liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f) $ do
|
|
|
|
moveAnnex k f
|
|
|
|
l <- calcGitLink f k
|
|
|
|
liftIO $ createSymbolicLink l f
|
|
|
|
showEndOk
|
|
|
|
|
|
|
|
cleandirect k = do
|
2013-02-14 20:17:40 +00:00
|
|
|
liftIO . nukeFile =<< inRepo (gitAnnexInodeCache k)
|
2012-12-13 19:44:56 +00:00
|
|
|
liftIO . nukeFile =<< inRepo (gitAnnexMapping k)
|
|
|
|
|
|
|
|
cleanup :: CommandCleanup
|
2012-12-13 20:00:17 +00:00
|
|
|
cleanup = do
|
2013-02-26 19:13:10 +00:00
|
|
|
setVersion defaultVersion
|
2012-12-13 20:00:17 +00:00
|
|
|
showStart "indirect" ""
|
|
|
|
showEndOk
|
|
|
|
return True
|