summaryrefslogtreecommitdiff
path: root/Annex/Export.hs
blob: 60039ef3b9bfabfc73ce475a26fddda1446d143d (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
{- git-annex exports
 -
 - Copyright 2017-2021 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU AGPL version 3 or higher.
 -}

{-# LANGUAGE OverloadedStrings #-}

module Annex.Export where

import Annex
import Annex.CatFile
import Types
import Types.Key
import qualified Git
import qualified Types.Remote as Remote
import Git.Quote
import Messages

import Data.Maybe
import qualified Data.ByteString.Short as S (fromShort, toShort)

-- From a sha pointing to the content of a file to the key
-- to use to export it. When the file is annexed, it's the annexed key.
-- When the file is stored in git, it's a special type of key to indicate
-- that.
exportKey :: Git.Sha -> Annex Key
exportKey sha = mk <$> catKey sha
  where
	mk (Just k) = k
	mk Nothing = gitShaKey sha

-- Encodes a git sha as a key. This is used to represent a non-annexed
-- file that is stored on a special remote, which necessarily needs a
-- key.
--
-- This is not the same as a SHA1 key, because the mapping needs to be
-- bijective, also because git may not always use SHA1, and because git
-- takes a SHA1 of the file size + content, while git-annex SHA1 keys
-- only checksum the content.
gitShaKey :: Git.Sha -> Key
gitShaKey (Git.Ref s) = mkKey $ \kd -> kd
	{ keyName = S.toShort s
	, keyVariety = OtherKey "GIT"
	}

-- Reverse of gitShaKey
keyGitSha :: Key -> Maybe Git.Sha
keyGitSha k
	| fromKey keyVariety k == OtherKey "GIT" =
		Just (Git.Ref (S.fromShort (fromKey keyName k)))
	| otherwise = Nothing

-- Is a key storing a git sha, and not used for an annexed file?
isGitShaKey :: Key -> Bool
isGitShaKey = isJust . keyGitSha

warnExportImportConflict :: Remote -> Annex ()
warnExportImportConflict r = do
	isimport <- Remote.isImportSupported r
	isexport <- Remote.isExportSupported r
	let (ops, resolvcmd) = case (isexport, isimport) of
		(False, True) -> ("imported from", "git-annex import")
		(True, False) -> ("exported to", "git-annex export")
		_ -> ("exported to and/or imported from", "git-annex export")
	toplevelWarning True $ UnquotedString $ unwords
		[ "Conflict detected. Different trees have been"
		, ops, Remote.name r ++ ". Use"
		, resolvcmd
		, "to resolve this conflict."
		]