git-annex/Command/Add.hs

129 lines
3.8 KiB
Haskell
Raw Normal View History

{- git-annex command
-
- Copyright 2010 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Add where
2011-10-05 20:02:51 +00:00
import Common.Annex
import Annex.Exception
import Command
import qualified Annex
2011-10-04 04:40:47 +00:00
import qualified Annex.Queue
import Types.KeySource
import Backend
2011-10-15 20:21:08 +00:00
import Logs.Location
2011-10-04 04:40:47 +00:00
import Annex.Content
import Annex.Perms
2011-08-20 20:11:42 +00:00
import Utility.Touch
import Utility.FileMode
def :: [Command]
def = [command "add" paramPaths seek "add files to annex"]
2010-11-11 22:54:52 +00:00
{- Add acts on both files not checked into git yet, and unlocked files. -}
seek :: [CommandSeek]
2010-11-11 22:54:52 +00:00
seek = [withFilesNotInGit start, withFilesUnlocked start]
{- The add subcommand annexes a file, storing it in a backend, and then
- moving it into the annex directory and setting up the symlink pointing
- to its content. -}
start :: FilePath -> CommandStart
start file = notBareRepo $ ifAnnexed file fixup add
where
add = do
s <- liftIO $ getSymbolicLinkStatus file
if isSymbolicLink s || not (isRegularFile s)
then stop
else do
showStart "add" file
next $ perform file
fixup (key, _) = do
-- 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
{- 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
- written to by a process that already has it open for writing. -}
2012-06-16 02:06:59 +00:00
lockDown :: FilePath -> Annex KeySource
2012-06-06 17:07:30 +00:00
lockDown file = do
liftIO $ preventWrite file
tmp <- fromRepo gitAnnexTmpDir
createAnnexDirectory tmp
2012-06-16 02:16:00 +00:00
liftIO $ do
(tmpfile, _handle) <- openTempFile tmp (takeFileName file)
nukeFile tmpfile
2012-06-16 02:16:00 +00:00
createLink file tmpfile
return $ KeySource { keyFilename = file , contentLocation = tmpfile }
2012-06-06 17:07:30 +00:00
2012-06-16 02:06:59 +00:00
{- Moves a locked down file into the annex. -}
ingest :: KeySource -> Annex (Maybe Key)
ingest source = do
backend <- chooseBackend $ keyFilename source
genKey source backend >>= go
2011-10-31 20:46:51 +00:00
where
2012-06-16 02:06:59 +00:00
go Nothing = do
liftIO $ nukeFile $ contentLocation source
return Nothing
go (Just (key, _)) = do
handle (undo (keyFilename source) key) $
moveAnnex key $ contentLocation source
liftIO $ nukeFile $ keyFilename source
2012-06-06 17:07:30 +00:00
return $ Just key
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
{- 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
where
-- fromAnnex could fail if the file ownership is weird
tryharder :: IOException -> Annex ()
tryharder _ = do
src <- inRepo $ gitAnnexLocation key
liftIO $ moveFile src file
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
liftIO $ createSymbolicLink l file
2012-06-06 17:07:30 +00:00
when hascontent $ do
logStatus key InfoPresent
2012-06-06 17:07:30 +00:00
-- 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
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
- create the symlink and add it. -}
cleanup :: FilePath -> Key -> Bool -> CommandCleanup
cleanup file key hascontent = do
_ <- link file key hascontent
params <- ifM (Annex.getState Annex.force)
( return [Param "-f"]
, return []
)
Annex.Queue.addCommand "add" (params++[Param "--"]) [file]
return True