aboutsummaryrefslogtreecommitdiff
path: root/Logs/Transfer.hs
blob: ab99304d1f1801ec7d54ad1431b5f98d4c074357 (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
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
{- git-annex transfer log files
 -
 - Copyright 2012 Joey Hess <joey@kitenet.net>
 -
 - Licensed under the GNU GPL version 3 or higher.
 -}

module Logs.Transfer where

import Common.Annex
import Types.Remote
import Remote
import Annex.Perms
import Annex.Exception
import qualified Git

import qualified Data.Map as M
import Control.Concurrent
import System.Posix.Process
import System.Posix.Types
import Data.Time.Clock

{- Enough information to uniquely identify a transfer, used as the filename
 - of the transfer information file. -}
data Transfer = Transfer Direction Remote Key
	deriving (Show)

{- Information about a Transfer, stored in the transfer information file. -}
data TransferInfo = TransferInfo
	{ transferPid :: Maybe ProcessID
	, transferThread :: Maybe ThreadId
	, startedTime :: UTCTime
	, bytesComplete :: Maybe Integer
	, associatedFile :: Maybe FilePath
	}
	deriving (Show)

data Direction = Upload | Download

instance Show Direction where
	show Upload = "upload"
	show Download = "download"

readDirection :: String -> Maybe Direction
readDirection "upload" = Just Upload
readDirection "download" = Just Download
readDirection _ = Nothing

{- Runs a transfer action. Creates and locks the transfer information file
 - while the action is running. Will throw an error if the transfer is
 - already in progress.
 -}
transfer :: Transfer -> Maybe FilePath -> Annex a -> Annex a
transfer transfer file a = do
	createAnnexDirectory =<< fromRepo gitAnnexTransferDir
	tfile <- fromRepo $ transferFile transfer
	mode <- annexFileMode
	info <- liftIO $ TransferInfo
		<$> pure Nothing -- pid not stored in file, so omitted for speed
		<*> pure Nothing -- threadid not stored in file, so omitted for speed
		<*> getCurrentTime
		<*> pure Nothing -- not 0; transfer may be resuming
		<*> pure file
	bracketIO (setup tfile mode info) (cleanup tfile) a
	where
		setup tfile mode info = do
			fd <- openFd tfile ReadWrite (Just mode)
				defaultFileFlags { trunc = True }
			locked <- catchMaybeIO $
				setLock fd (WriteLock, AbsoluteSeek, 0, 0)
			when (locked == Nothing) $
				error $ "transfer already in progress"
			fdWrite fd $ writeTransferInfo info
			return fd
		cleanup tfile fd = do
			removeFile tfile
			closeFd fd

{- If a transfer is still running, returns its TransferInfo. -}
checkTransfer :: Transfer -> Annex (Maybe TransferInfo)
checkTransfer transfer = do
	mode <- annexFileMode
	tfile <- fromRepo $ transferFile transfer
	mfd <- liftIO $ catchMaybeIO $
		openFd tfile ReadOnly (Just mode) defaultFileFlags
	case mfd of
		Nothing -> return Nothing -- failed to open file; not running
		Just fd -> do
			locked <- liftIO $
				getLock fd (WriteLock, AbsoluteSeek, 0, 0)
			case locked of
				Nothing -> do
					liftIO $ closeFd fd
					return Nothing
				Just (pid, _) -> liftIO $ do
					handle <- fdToHandle fd
					info <- readTransferInfo pid
						<$> hGetContentsStrict handle
					closeFd fd
					return info

{- Gets all currently running transfers. -}
getTransfers :: Annex [(Transfer, TransferInfo)]
getTransfers = do
	uuidmap <- remoteMap id
	transfers <- catMaybes . map (parseTransferFile uuidmap) <$> findfiles
	infos <- mapM checkTransfer transfers
	return $ map (\(t, Just i) -> (t, i)) $
		filter running $ zip transfers infos
	where
		findfiles = liftIO . dirContentsRecursive
			=<< fromRepo gitAnnexTransferDir
		running (_, i) = isJust i

{- The transfer information file to use for a given Transfer. -}
transferFile :: Transfer -> Git.Repo -> FilePath
transferFile (Transfer direction remote key) repo = 
	gitAnnexTransferDir repo 
		</> show direction 
		</> show (uuid remote) 
		</> keyFile key

{- Parses a transfer information filename to a Transfer. -}
parseTransferFile :: M.Map UUID Remote -> FilePath -> Maybe Transfer
parseTransferFile uuidmap file = 
	case drop (length bits - 3) bits of
		[direction, uuid, key] -> Transfer
			<$> readDirection direction
			<*> M.lookup (toUUID uuid) uuidmap
			<*> fileKey key
		_ -> Nothing
	where
		bits = splitDirectories file

writeTransferInfo :: TransferInfo -> String
writeTransferInfo info = unwords
	-- transferPid is not included; instead obtained by looking at
	-- the process that locks the file.
	-- transferThread is not included; not relevant for other processes
	[ show $ startedTime info
	-- bytesComplete is not included; changes too fast 
	, fromMaybe "" $ associatedFile info -- comes last, may contain spaces
	]

readTransferInfo :: ProcessID -> String -> Maybe TransferInfo
readTransferInfo pid s =
	case bits of
		[time] -> TransferInfo
			<$> pure (Just pid)
			<*> pure Nothing
			<*> readish time
			<*> pure Nothing
			<*> pure filename
		_ -> Nothing
	where
		(bits, filebits) = splitAt 1 $ split " " s 
		filename
			| null filebits = Nothing
			| otherwise = Just $ join " " filebits