2010-11-02 23:04:24 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
|
|
|
- Copyright 2010 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-02-10 19:48:38 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2010-11-02 23:04:24 +00:00
|
|
|
module Command.Add where
|
|
|
|
|
2011-10-05 20:02:51 +00:00
|
|
|
import Common.Annex
|
2011-10-04 04:34:04 +00:00
|
|
|
import Annex.Exception
|
2010-11-02 23:04:24 +00:00
|
|
|
import Command
|
2012-06-20 20:07:14 +00:00
|
|
|
import Types.KeySource
|
2012-06-05 23:51:03 +00:00
|
|
|
import Backend
|
2011-10-15 20:21:08 +00:00
|
|
|
import Logs.Location
|
2011-10-04 04:40:47 +00:00
|
|
|
import Annex.Content
|
2012-12-24 17:37:29 +00:00
|
|
|
import Annex.Content.Direct
|
2012-06-06 00:28:34 +00:00
|
|
|
import Annex.Perms
|
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 Annex.Link
|
|
|
|
import qualified Annex
|
|
|
|
import qualified Annex.Queue
|
2013-02-27 06:39:22 +00:00
|
|
|
#ifndef __ANDROID__
|
2011-08-20 20:11:42 +00:00
|
|
|
import Utility.Touch
|
2013-02-10 19:48:38 +00:00
|
|
|
#endif
|
2012-06-06 00:28:34 +00:00
|
|
|
import Utility.FileMode
|
2012-12-24 17:37:29 +00:00
|
|
|
import Config
|
2013-02-14 20:54:36 +00:00
|
|
|
import Utility.InodeCache
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2011-10-29 19:19:05 +00:00
|
|
|
def :: [Command]
|
2013-01-06 21:24:22 +00:00
|
|
|
def = [notBareRepo $ command "add" paramPaths seek "add files to annex"]
|
2010-12-30 18:19:16 +00:00
|
|
|
|
2013-02-20 18:12:55 +00:00
|
|
|
{- Add acts on both files not checked into git yet, and unlocked files.
|
|
|
|
-
|
|
|
|
- In direct mode, it acts on any files that have changed. -}
|
2010-12-30 18:19:16 +00:00
|
|
|
seek :: [CommandSeek]
|
2013-01-06 21:24:22 +00:00
|
|
|
seek =
|
|
|
|
[ withFilesNotInGit start
|
2013-02-20 18:12:55 +00:00
|
|
|
, whenNotDirect $ withFilesUnlocked start
|
|
|
|
, whenDirect $ withFilesMaybeModified start
|
2013-01-06 21:24:22 +00:00
|
|
|
]
|
2010-11-11 22:54:52 +00:00
|
|
|
|
2012-12-19 16:50:24 +00:00
|
|
|
{- The add subcommand annexes a file, generating a key for it using a
|
|
|
|
- backend, and then moving it into the annex directory and setting up
|
|
|
|
- the symlink pointing to its content. -}
|
2012-02-14 03:42:44 +00:00
|
|
|
start :: FilePath -> CommandStart
|
2013-02-20 17:37:46 +00:00
|
|
|
start file = ifAnnexed file addpresent add
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
add = do
|
|
|
|
s <- liftIO $ getSymbolicLinkStatus file
|
|
|
|
if isSymbolicLink s || not (isRegularFile s)
|
|
|
|
then stop
|
|
|
|
else do
|
|
|
|
showStart "add" file
|
|
|
|
next $ perform file
|
2013-02-20 17:37:46 +00:00
|
|
|
addpresent (key, _) = ifM isDirect
|
|
|
|
( ifM (goodContent key file) ( stop , add )
|
|
|
|
, fixup key
|
|
|
|
)
|
|
|
|
fixup key = do
|
2012-11-12 05:05:04 +00:00
|
|
|
-- fixup from an interrupted add; the symlink
|
|
|
|
-- is present but not yet added to git
|
|
|
|
showStart "add" file
|
|
|
|
liftIO $ removeFile file
|
|
|
|
next $ next $ cleanup file key =<< inAnnex key
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2012-06-06 00:28:34 +00:00
|
|
|
{- The file that's being added is locked down before a key is generated,
|
|
|
|
- to prevent it from being modified in between. It's hard linked into a
|
|
|
|
- temporary location, and its writable bits are removed. It could still be
|
2013-01-14 19:02:13 +00:00
|
|
|
- written to by a process that already has it open for writing.
|
|
|
|
-
|
|
|
|
- Lockdown can fail if a file gets deleted, and Nothing will be returned.
|
|
|
|
-}
|
|
|
|
lockDown :: FilePath -> Annex (Maybe KeySource)
|
2013-02-14 18:10:36 +00:00
|
|
|
lockDown file = ifM (crippledFileSystem)
|
2013-02-14 20:54:36 +00:00
|
|
|
( liftIO $ catchMaybeIO $ do
|
|
|
|
cache <- genInodeCache file
|
|
|
|
return $ KeySource
|
|
|
|
{ keyFilename = file
|
|
|
|
, contentLocation = file
|
|
|
|
, inodeCache = cache
|
|
|
|
}
|
2013-02-14 18:10:36 +00:00
|
|
|
, do
|
|
|
|
tmp <- fromRepo gitAnnexTmpDir
|
|
|
|
createAnnexDirectory tmp
|
|
|
|
liftIO $ catchMaybeIO $ do
|
|
|
|
preventWrite file
|
|
|
|
(tmpfile, h) <- openTempFile tmp (takeFileName file)
|
|
|
|
hClose h
|
|
|
|
nukeFile tmpfile
|
|
|
|
createLink file tmpfile
|
2013-02-14 20:54:36 +00:00
|
|
|
cache <- genInodeCache tmpfile
|
|
|
|
return $ KeySource
|
|
|
|
{ keyFilename = file
|
|
|
|
, contentLocation = tmpfile
|
|
|
|
, inodeCache = cache
|
|
|
|
}
|
2013-02-14 18:10:36 +00:00
|
|
|
)
|
2012-06-06 17:07:30 +00:00
|
|
|
|
2013-02-14 18:10:36 +00:00
|
|
|
{- Ingests a locked down file into the annex.
|
2012-12-24 17:37:29 +00:00
|
|
|
-
|
2013-01-06 21:24:22 +00:00
|
|
|
- In direct mode, leaves the file alone, and just updates bookkeeping
|
2012-12-24 17:37:29 +00:00
|
|
|
- information.
|
|
|
|
-}
|
2013-01-14 19:02:13 +00:00
|
|
|
ingest :: (Maybe KeySource) -> Annex (Maybe Key)
|
|
|
|
ingest Nothing = return Nothing
|
|
|
|
ingest (Just source) = do
|
2012-06-16 02:06:59 +00:00
|
|
|
backend <- chooseBackend $ keyFilename source
|
2013-02-14 20:54:36 +00:00
|
|
|
k <- genKey source backend
|
|
|
|
cache <- liftIO $ genInodeCache $ contentLocation source
|
|
|
|
case inodeCache source of
|
|
|
|
Nothing -> go k cache
|
|
|
|
Just c
|
|
|
|
| (Just c == cache) -> go k cache
|
|
|
|
| otherwise -> failure
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
2013-02-14 20:54:36 +00:00
|
|
|
go k cache = ifM isDirect ( godirect k cache , goindirect k cache )
|
|
|
|
|
|
|
|
goindirect (Just (key, _)) _ = do
|
2012-12-29 19:32:29 +00:00
|
|
|
handle (undo (keyFilename source) key) $
|
|
|
|
moveAnnex key $ contentLocation source
|
|
|
|
liftIO $ nukeFile $ keyFilename source
|
|
|
|
return $ Just key
|
2013-02-14 20:54:36 +00:00
|
|
|
goindirect Nothing _ = failure
|
2012-12-29 19:32:29 +00:00
|
|
|
|
2013-02-14 20:54:36 +00:00
|
|
|
godirect (Just (key, _)) (Just cache) = do
|
|
|
|
writeInodeCache key cache
|
|
|
|
void $ addAssociatedFile key $ keyFilename source
|
|
|
|
unlessM crippledFileSystem $
|
|
|
|
liftIO $ allowWrite $ keyFilename source
|
|
|
|
when (contentLocation source /= keyFilename source) $
|
|
|
|
liftIO $ nukeFile $ contentLocation source
|
|
|
|
return $ Just key
|
2012-12-29 19:32:29 +00:00
|
|
|
godirect _ _ = failure
|
|
|
|
|
|
|
|
failure = do
|
2013-02-14 18:10:36 +00:00
|
|
|
when (contentLocation source /= keyFilename source) $
|
|
|
|
liftIO $ nukeFile $ contentLocation source
|
2012-12-29 19:32:29 +00:00
|
|
|
return Nothing
|
2010-11-02 23:04:24 +00:00
|
|
|
|
2012-06-06 17:07:30 +00:00
|
|
|
perform :: FilePath -> CommandPerform
|
2012-06-16 02:06:59 +00:00
|
|
|
perform file =
|
|
|
|
maybe stop (\key -> next $ cleanup file key True)
|
|
|
|
=<< ingest =<< lockDown file
|
2012-06-06 00:28:34 +00:00
|
|
|
|
2011-07-08 01:29:31 +00:00
|
|
|
{- On error, put the file back so it doesn't seem to have vanished.
|
|
|
|
- This can be called before or after the symlink is in place. -}
|
|
|
|
undo :: FilePath -> Key -> IOException -> Annex a
|
|
|
|
undo file key e = do
|
2012-03-06 18:12:15 +00:00
|
|
|
whenM (inAnnex key) $ do
|
2012-06-06 17:13:13 +00:00
|
|
|
liftIO $ nukeFile file
|
2012-03-06 18:12:15 +00:00
|
|
|
handle tryharder $ fromAnnex key file
|
|
|
|
logStatus key InfoMissing
|
|
|
|
throw e
|
2012-11-12 05:05:04 +00:00
|
|
|
where
|
|
|
|
-- fromAnnex could fail if the file ownership is weird
|
|
|
|
tryharder :: IOException -> Annex ()
|
|
|
|
tryharder _ = do
|
|
|
|
src <- inRepo $ gitAnnexLocation key
|
|
|
|
liftIO $ moveFile src file
|
2011-07-07 23:29:36 +00:00
|
|
|
|
2012-06-19 06:40:21 +00:00
|
|
|
{- Creates the symlink to the annexed content, returns the link target. -}
|
|
|
|
link :: FilePath -> Key -> Bool -> Annex String
|
2012-06-06 17:07:30 +00:00
|
|
|
link file key hascontent = handle (undo file key) $ do
|
|
|
|
l <- calcGitLink file key
|
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
|
|
|
makeAnnexLink l file
|
2011-08-06 18:57:22 +00:00
|
|
|
|
2013-02-27 06:39:22 +00:00
|
|
|
#ifndef __ANDROID__
|
2012-06-06 17:07:30 +00:00
|
|
|
when hascontent $ do
|
|
|
|
-- touch the symlink to have the same mtime as the
|
|
|
|
-- file it points to
|
|
|
|
liftIO $ do
|
|
|
|
mtime <- modificationTime <$> getFileStatus file
|
|
|
|
touch file (TimeSpec mtime) False
|
2013-02-10 19:48:38 +00:00
|
|
|
#endif
|
2011-03-15 03:00:23 +00:00
|
|
|
|
2012-06-19 06:40:21 +00:00
|
|
|
return l
|
|
|
|
|
2012-06-06 17:07:30 +00:00
|
|
|
{- Note: Several other commands call this, and expect it to
|
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
|
|
|
- create the link and add it.
|
|
|
|
-
|
|
|
|
- In direct mode, when we have the content of the file, it's left as-is,
|
|
|
|
- and we just stage a symlink to git.
|
|
|
|
-
|
|
|
|
- Otherwise, as long as the filesystem supports symlinks, we use
|
|
|
|
- git add, rather than directly staging the symlink to git.
|
|
|
|
- Using git add is best because it allows the queuing to work
|
|
|
|
- and is faster (staging the symlink runs hash-object commands each time).
|
|
|
|
- Also, using git add allows it to skip gitignored files, unless forced
|
|
|
|
- to include them.
|
|
|
|
-}
|
2012-06-06 17:07:30 +00:00
|
|
|
cleanup :: FilePath -> Key -> Bool -> CommandCleanup
|
2013-02-05 17:41:48 +00:00
|
|
|
cleanup file key hascontent = do
|
|
|
|
when hascontent $
|
|
|
|
logStatus key InfoPresent
|
|
|
|
ifM (isDirect <&&> pure hascontent)
|
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
|
|
|
( stageSymlink file =<< hashSymlink =<< calcGitLink file key
|
|
|
|
, ifM (coreSymlinks <$> Annex.getGitConfig)
|
|
|
|
( do
|
|
|
|
_ <- link file key hascontent
|
|
|
|
params <- ifM (Annex.getState Annex.force)
|
|
|
|
( return [Param "-f"]
|
|
|
|
, return []
|
|
|
|
)
|
|
|
|
Annex.Queue.addCommand "add" (params++[Param "--"]) [file]
|
|
|
|
, do
|
|
|
|
l <- link file key hascontent
|
|
|
|
addAnnexLink l file
|
|
|
|
)
|
2013-02-05 17:41:48 +00:00
|
|
|
)
|
|
|
|
return True
|