1{- git-annex remotes types
2 -
3 - Most things should not need this, using Types instead
4 -
5 - Copyright 2011-2021 Joey Hess <id@joeyh.name>
6 -
7 - Licensed under the GNU AGPL version 3 or higher.
8 -}
9
10{-# LANGUAGE RankNTypes #-}
11
12module Types.Remote
13	( module Types.RemoteConfig
14	, RemoteTypeA(..)
15	, RemoteA(..)
16	, RemoteStateHandle
17	, SetupStage(..)
18	, Availability(..)
19	, VerifyConfigA(..)
20	, Verification(..)
21	, unVerified
22	, RetrievalSecurityPolicy(..)
23	, isExportSupported
24	, isImportSupported
25	, ExportActions(..)
26	, ImportActions(..)
27	, ByteSize
28	)
29	where
30
31import Data.Ord
32
33import qualified Git
34import Types.Key
35import Types.UUID
36import Types.GitConfig
37import Types.Availability
38import Types.Creds
39import Types.RemoteState
40import Types.UrlContents
41import Types.NumCopies
42import Types.Export
43import Types.Import
44import Types.RemoteConfig
45import Utility.Hash (IncrementalVerifier)
46import Config.Cost
47import Utility.Metered
48import Git.Types (RemoteName)
49import Utility.SafeCommand
50import Utility.Url
51import Utility.DataUnits
52
53data SetupStage = Init | Enable RemoteConfig | AutoEnable RemoteConfig
54
55{- There are different types of remotes. -}
56data RemoteTypeA a = RemoteType
57	-- human visible type name
58	{ typename :: String
59	-- enumerates remotes of this type
60	-- The Bool is True if automatic initialization of remotes is desired
61	, enumerate :: Bool -> a [Git.Repo]
62	-- generates a remote of this type
63	, generate :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> RemoteStateHandle -> a (Maybe (RemoteA a))
64	-- parse configs of remotes of this type
65	, configParser :: RemoteConfig -> a RemoteConfigParser
66	-- initializes or enables a remote
67	, setup :: SetupStage -> Maybe UUID -> Maybe CredPair -> RemoteConfig -> RemoteGitConfig -> a (RemoteConfig, UUID)
68	-- check if a remote of this type is able to support export
69	, exportSupported :: ParsedRemoteConfig -> RemoteGitConfig -> a Bool
70	-- check if a remote of this type is able to support import
71	, importSupported :: ParsedRemoteConfig -> RemoteGitConfig -> a Bool
72	-- is a remote of this type not a usual key/value store,
73	-- or export/import of a tree of files, but instead a collection
74	-- of files, populated by something outside git-annex, some of
75	-- which may be annex objects?
76	, thirdPartyPopulated :: Bool
77	}
78
79instance Eq (RemoteTypeA a) where
80	x == y = typename x == typename y
81
82{- An individual remote. -}
83data RemoteA a = Remote
84	-- each Remote has a unique uuid
85	{ uuid :: UUID
86	-- each Remote has a human visible name
87	, name :: RemoteName
88	-- Remotes have a use cost; higher is more expensive
89	, cost :: Cost
90	-- Transfers a key's contents from disk to the remote.
91	-- The key should not appear to be present on the remote until
92	-- all of its contents have been transferred.
93	-- Throws exception on failure.
94	, storeKey :: Key -> AssociatedFile -> MeterUpdate -> a ()
95	-- Retrieves a key's contents to a file.
96	-- (The MeterUpdate does not need to be used if it writes
97	-- sequentially to the file.)
98	-- Throws exception on failure.
99	, retrieveKeyFile :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> VerifyConfigA a -> a Verification
100	-- Retrieves a key's contents to a tmp file, if it can be done cheaply.
101	-- It's ok to create a symlink or hardlink.
102	-- Throws exception on failure.
103	, retrieveKeyFileCheap :: Maybe (Key -> AssociatedFile -> FilePath -> a ())
104	-- Security policy for reteiving keys from this remote.
105	, retrievalSecurityPolicy :: RetrievalSecurityPolicy
106	-- Removes a key's contents (succeeds even the contents are not present)
107	-- Can throw exception if unable to access remote, or if remote
108	-- refuses to remove the content.
109	, removeKey :: Key -> a ()
110	-- Uses locking to prevent removal of a key's contents,
111	-- thus producing a VerifiedCopy, which is passed to the callback.
112	-- If unable to lock, does not run the callback, and throws an
113	-- exception.
114	-- This is optional; remotes do not have to support locking.
115	, lockContent :: forall r. Maybe (Key -> (VerifiedCopy -> a r) -> a r)
116	-- Checks if a key is present in the remote.
117	-- Throws an exception if the remote cannot be accessed.
118	, checkPresent :: Key -> a Bool
119	-- Some remotes can checkPresent without an expensive network
120	-- operation.
121	, checkPresentCheap :: Bool
122	-- Some remotes support export.
123	, exportActions :: ExportActions a
124	-- Some remotes support import.
125	, importActions :: ImportActions a
126	-- Some remotes can provide additional details for whereis.
127	, whereisKey :: Maybe (Key -> a [String])
128	-- Some remotes can run a fsck operation on the remote,
129	-- without transferring all the data to the local repo
130	-- The parameters are passed to the fsck command on the remote.
131	, remoteFsck :: Maybe ([CommandParam] -> a (IO Bool))
132	-- Runs an action to repair the remote's git repository.
133	, repairRepo :: Maybe (a Bool -> a (IO Bool))
134	-- a Remote has a persistent configuration store
135	, config :: ParsedRemoteConfig
136	-- Get the git repo for the Remote.
137	, getRepo :: a Git.Repo
138	-- a Remote's configuration from git
139	, gitconfig :: RemoteGitConfig
140	-- a Remote can be assocated with a specific local filesystem path
141	, localpath :: Maybe FilePath
142	-- a Remote can be known to be readonly
143	, readonly :: Bool
144	-- a Remote can allow writes but not have a way to delete content
145	-- from it.
146	, appendonly :: Bool
147	-- Set if a remote cannot be trusted to continue to contain the
148	-- contents of files stored there. Notably, most export/import
149	-- remotes are untrustworthy because they are not key/value stores.
150	-- Since this prevents the user from adjusting a remote's trust
151	-- level, it's often better not not set it and instead let the user
152	-- decide.
153	, untrustworthy :: Bool
154	-- a Remote can be globally available. (Ie, "in the cloud".)
155	, availability :: Availability
156	-- the type of the remote
157	, remotetype :: RemoteTypeA a
158	-- For testing, makes a version of this remote that is not
159	-- available for use. All its actions should fail.
160	, mkUnavailable :: a (Maybe (RemoteA a))
161	-- Information about the remote, for git annex info to display.
162	, getInfo :: a [(String, String)]
163	-- Some remotes can download from an url (or uri). This asks the
164	-- remote if it can handle a particular url. The actual download
165	-- will be done using retrieveKeyFile, and the remote can look up
166	-- up the url to download for a key using Logs.Web.getUrls.
167	, claimUrl :: Maybe (URLString -> a Bool)
168	-- Checks that the url is accessible, and gets information about
169	-- its contents, without downloading the full content.
170	-- Throws an exception if the url is inaccessible.
171	, checkUrl :: Maybe (URLString -> a UrlContents)
172	, remoteStateHandle :: RemoteStateHandle
173	}
174
175instance RemoteNameable (RemoteA a) where
176	getRemoteName = name
177
178instance Show (RemoteA a) where
179	show remote = "Remote { name =\"" ++ name remote ++ "\" }"
180
181-- two remotes are the same if they have the same uuid
182instance Eq (RemoteA a) where
183	x == y = uuid x == uuid y
184
185-- Order by cost since that is the important order of remotes
186-- when deciding which to use. But since remotes often have the same cost
187-- and Ord must be total, do a secondary ordering by uuid.
188instance Ord (RemoteA a) where
189	compare a b
190		| cost a == cost b = comparing uuid a b
191		| otherwise = comparing cost a b
192
193instance ToUUID (RemoteA a) where
194	toUUID = uuid
195
196data VerifyConfigA a
197	= AlwaysVerify
198	| NoVerify
199	| RemoteVerify (RemoteA a)
200	| DefaultVerify
201
202data Verification
203	= UnVerified
204	-- ^ Content was not verified during transfer, but is probably
205	-- ok, so if verification is disabled, don't verify it
206	| Verified
207	-- ^ Content was verified during transfer, so don't verify it
208	-- again. The verification does not need to use a
209	-- cryptographically secure hash, but the hash does need to
210	-- have preimage resistance.
211	| MustVerify
212	-- ^ Content likely to have been altered during transfer,
213	-- verify even if verification is normally disabled
214	| IncompleteVerify IncrementalVerifier
215	-- ^ Content was partially verified during transfer, but
216	-- the verification is not complete.
217
218unVerified :: Monad m => m a -> m (a, Verification)
219unVerified a = do
220	ok <- a
221	return (ok, UnVerified)
222
223-- Security policy indicating what keys can be safely retrieved from a
224-- remote.
225data RetrievalSecurityPolicy
226	= RetrievalVerifiableKeysSecure
227	-- ^ Transfer of keys whose content can be verified
228	-- with a hash check is secure; transfer of unverifiable keys is
229	-- not secure and should not be allowed.
230	--
231	-- This is used eg, when HTTP to a remote could be redirected to a
232	-- local private web server or even a file:// url, causing private
233	-- data from it that is not the intended content of a key to make
234	-- its way into the git-annex repository.
235	--
236	-- It's also used when content is stored encrypted on a remote,
237	-- which could replace it with a different encrypted file, and
238	-- trick git-annex into decrypting it and leaking the decryption
239	-- into the git-annex repository.
240	--
241	-- It's not (currently) used when the remote could alter the
242	-- content stored on it, because git-annex does not provide
243	-- strong guarantees about the content of keys that cannot be
244	-- verified with a hash check.
245	-- (But annex.securehashesonly does provide such guarantees.)
246	| RetrievalAllKeysSecure
247	-- ^ Any key can be securely retrieved.
248
249isExportSupported :: RemoteA a -> a Bool
250isExportSupported r = exportSupported (remotetype r) (config r) (gitconfig r)
251
252isImportSupported :: RemoteA a -> a Bool
253isImportSupported r = importSupported (remotetype r) (config r) (gitconfig r)
254
255data ExportActions a = ExportActions
256	-- Exports content to an ExportLocation.
257	-- The exported file should not appear to be present on the remote
258	-- until all of its contents have been transferred.
259	-- Throws exception on failure.
260	{ storeExport :: FilePath -> Key -> ExportLocation -> MeterUpdate -> a ()
261	-- Retrieves exported content to a file.
262	-- (The MeterUpdate does not need to be used if it writes
263	-- sequentially to the file.)
264	-- Throws exception on failure.
265	, retrieveExport :: Key -> ExportLocation -> FilePath -> MeterUpdate -> a ()
266	-- Removes an exported file (succeeds if the contents are not present)
267	-- Can throw exception if unable to access remote, or if remote
268	-- refuses to remove the content.
269	, removeExport :: Key -> ExportLocation -> a ()
270	-- Set when the content of a Key stored in the remote to an
271	-- ExportLocation and then removed with removeExport remains
272	-- accessible to retrieveKeyFile and checkPresent.
273	, versionedExport :: Bool
274	-- Removes an exported directory. Typically the directory will be
275	-- empty, but it could possibly contain files or other directories,
276	-- and it's ok to delete those (but not required to).
277	-- If the remote does not use directories, or automatically cleans
278	-- up empty directories, this can be Nothing.
279	--
280	-- Should not fail if the directory was already removed.
281	--
282	-- Throws exception if unable to contact the remote, or perhaps if
283	-- the remote refuses to let the directory be removed.
284	, removeExportDirectory :: Maybe (ExportDirectory -> a ())
285	-- Checks if anything is exported to the remote at the specified
286	-- ExportLocation. It may check the size or other characteristics
287	-- of the Key, but does not need to guarantee that the content on
288	-- the remote is the same as the Key's content.
289	-- Throws an exception if the remote cannot be accessed.
290	, checkPresentExport :: Key -> ExportLocation -> a Bool
291	-- Renames an already exported file.
292	--
293	-- If the remote does not support the requested rename,
294	-- it can return Nothing. It's ok if the remove deletes
295	-- the file in such a situation too; it will be re-exported to
296	-- recover.
297	--
298	-- Throws an exception if the remote cannot be accessed, or
299	-- the file doesn't exist or cannot be renamed.
300	, renameExport :: Key -> ExportLocation -> ExportLocation -> a (Maybe ())
301	}
302
303data ImportActions a = ImportActions
304	-- Finds the current set of files that are stored in the remote,
305	-- along with their content identifiers and size.
306	--
307	-- May also find old versions of files that are still stored in the
308	-- remote.
309	--
310	-- Throws exception on failure to access the remote.
311	-- May return Nothing when the remote is unchanged since last time.
312	{ listImportableContents :: a (Maybe (ImportableContents (ContentIdentifier, ByteSize)))
313	-- Generates a Key (of any type) for the file stored on the
314	-- remote at the ImportLocation. Does not download the file
315	-- from the remote.
316	--
317	-- May update the progress meter if it needs to perform an
318	-- expensive operation, such as hashing a local file.
319	--
320	-- Ensures that the key corresponds to the ContentIdentifier,
321	-- bearing in mind that the file on the remote may have changed
322	-- since the ContentIdentifier was generated.
323	--
324	-- When it returns nothing, the file at the ImportLocation
325	-- not by included in the imported tree.
326	--
327	-- When the remote is thirdPartyPopulated, this should check if the
328	-- file stored on the remote is the content of an annex object,
329	-- and return its Key, or Nothing if it is not.
330	--
331	-- Throws exception on failure to access the remote.
332	, importKey :: Maybe (ImportLocation -> ContentIdentifier -> ByteSize -> MeterUpdate -> a (Maybe Key))
333	-- Retrieves a file from the remote. Ensures that the file
334	-- it retrieves has the requested ContentIdentifier.
335	--
336	-- This has to be used rather than retrieveExport
337	-- when a special remote supports imports, since files on such a
338	-- special remote can be changed at any time.
339	--
340	-- Throws exception on failure.
341	, retrieveExportWithContentIdentifier
342		:: ExportLocation
343		-> ContentIdentifier
344		-- file to write content to
345		-> FilePath
346		-- callback that generates a key from the downloaded content
347		-> a Key
348		-> MeterUpdate
349		-> a Key
350	-- Exports content to an ExportLocation, and returns the
351	-- ContentIdentifier corresponding to the content it stored.
352	--
353	-- This is used rather than storeExport when a special remote
354	-- supports imports, since files on such a special remote can be
355	-- changed at any time.
356	--
357	-- Since other things can modify the same file on the special
358	-- remote, this must take care to not overwrite such modifications,
359	-- and only overwrite a file that has one of the ContentIdentifiers
360	-- passed to it, unless listContents can recover an overwritten file.
361	--
362	-- Also, since there can be concurrent writers, the implementation
363	-- needs to make sure that the ContentIdentifier it returns
364	-- corresponds to what it wrote, not to what some other writer
365	-- wrote.
366	--
367	-- Throws exception on failure.
368	, storeExportWithContentIdentifier
369		:: FilePath
370		-> Key
371		-> ExportLocation
372		-- old content that it's safe to overwrite
373		-> [ContentIdentifier]
374		-> MeterUpdate
375		-> a ContentIdentifier
376	-- This is used rather than removeExport when a special remote
377	-- supports imports.
378	--
379	-- It should only remove a file from the remote when it has one
380	-- of the ContentIdentifiers passed to it, unless listContents
381	-- can recover an overwritten file.
382	--
383	-- It needs to handle races similar to storeExportWithContentIdentifier.
384	--
385	-- Throws an exception when unable to remove.
386	, removeExportWithContentIdentifier
387		:: Key
388		-> ExportLocation
389		-> [ContentIdentifier]
390		-> a ()
391	-- Removes a directory from the export, but only when it's empty.
392	-- Used instead of removeExportDirectory when a special remote
393	-- supports imports.
394	--
395	-- If the directory is not empty, it should succeed.
396	--
397	-- Throws exception if unable to contact the remote, or perhaps if
398	-- the remote refuses to let the directory be removed.
399	, removeExportDirectoryWhenEmpty :: Maybe (ExportDirectory -> a ())
400	-- Checks if the specified ContentIdentifier is exported to the
401	-- remote at the specified ExportLocation.
402	-- Throws an exception if the remote cannot be accessed.
403	, checkPresentExportWithContentIdentifier
404		:: Key
405		-> ExportLocation
406		-> [ContentIdentifier]
407		-> a Bool
408	}
409
410