aboutsummaryrefslogtreecommitdiff
path: root/Command/Add.hs
blob: d83817d729271e28d9ff9db990425cdeebeed762 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
{- git-annex command
 -
 - Copyright 2010 Joey Hess <joey@kitenet.net>
 -
 - Licensed under the GNU GPL version 3 or higher.
 -}

module Command.Add where

import Common.Annex
import Annex.Exception
import Command
import qualified Annex
import qualified Annex.Queue
import Backend
import Logs.Location
import Annex.Content
import Annex.Perms
import Utility.Touch
import Utility.FileMode

def :: [Command]
def = [command "add" paramPaths seek "add files to annex"]

{- Add acts on both files not checked into git yet, and unlocked files. -}
seek :: [CommandSeek]
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. -}
lockDown :: FilePath -> Annex FilePath
lockDown file = do
	liftIO $ preventWrite file
	tmp <- fromRepo gitAnnexTmpDir
	createAnnexDirectory tmp
	pid <- liftIO getProcessID
	let tmpfile = tmp </> "add" ++ show pid ++ "." ++ takeFileName file
	liftIO $ nukeFile tmpfile
	liftIO $ createLink file tmpfile
	return tmpfile

{- Moves the file into the annex. -}
ingest :: FilePath -> Annex (Maybe Key)
ingest file = do
	tmpfile <- lockDown file
	let source = KeySource { keyFilename = file, contentLocation = tmpfile }
	backend <- chooseBackend file
	genKey source backend >>= go tmpfile
	where
		go _ Nothing = return Nothing
		go tmpfile (Just (key, _)) = do
			handle (undo file key) $ moveAnnex key tmpfile
			liftIO $ nukeFile file
			return $ Just key

perform :: FilePath -> CommandPerform
perform file = maybe stop (\key -> next $ cleanup file key True) =<< ingest 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
	whenM (inAnnex key) $ do
		liftIO $ nukeFile file
		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

{- Creates the symlink to the annexed content. -}
link :: FilePath -> Key -> Bool -> Annex ()
link file key hascontent = handle (undo file key) $ do
	l <- calcGitLink file key
	liftIO $ createSymbolicLink l file

	when hascontent $ do
		logStatus key InfoPresent
	
		-- 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

{- 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.add "add" (params++[Param "--"]) [file]
	return True