File: RenameRemote.hs

package info (click to toggle)
git-annex 8.20210223-2
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 68,764 kB
  • sloc: haskell: 70,359; javascript: 9,103; sh: 1,304; makefile: 212; perl: 136; ansic: 44
file content (57 lines) | stat: -rw-r--r-- 1,905 bytes parent folder | download
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
{- git-annex command
 -
 - Copyright 2019 Joey Hess <id@joeyh.name>
 -
 - Licensed under the GNU AGPL version 3 or higher.
 -}

module Command.RenameRemote where

import Command
import qualified Annex.SpecialRemote
import Annex.SpecialRemote.Config (nameField, sameasNameField)
import qualified Logs.Remote
import qualified Types.Remote as R
import qualified Remote
import Types.ProposedAccepted

import qualified Data.Map as M

cmd :: Command
cmd = command "renameremote" SectionSetup
	"changes name of special remote"
	(paramPair paramName paramName)
	(withParams seek)

seek :: CmdParams -> CommandSeek
seek = withWords (commandAction . start)

start :: [String] -> CommandStart
start ps@(oldname:newname:[]) = Annex.SpecialRemote.findExisting oldname >>= \case
	Just (u, cfg, mcu) -> Annex.SpecialRemote.findExisting newname >>= \case
		Just _ -> giveup $ "The name " ++ newname ++ " is already used by a special remote."
		Nothing -> go u cfg mcu
	-- Support lookup by uuid or description as well as remote name,
	-- as a fallback when there is nothing with the name in the
	-- special remote log.
	Nothing -> Remote.nameToUUID' oldname >>= \case
		Left e -> giveup e
		Right u -> do
			m <- Logs.Remote.remoteConfigMap
			case M.lookup u m of
				Nothing -> giveup "That is not a special remote."
				Just cfg -> go u cfg Nothing
  where
	ai = ActionItemOther Nothing
	si = SeekInput ps
	go u cfg mcu = starting "rename" ai si $ perform u cfg mcu newname
start _ = giveup "Specify an old name (or uuid or description) and a new name."

perform :: UUID -> R.RemoteConfig -> Maybe (Annex.SpecialRemote.ConfigFrom UUID) -> String -> CommandPerform
perform u cfg mcu newname = do
	let (namefield, cu) = case mcu of
		Nothing -> (nameField, u)
		Just (Annex.SpecialRemote.ConfigFrom u') -> (sameasNameField, u')
	Logs.Remote.configSet cu (M.insert namefield (Proposed newname) cfg)
	
	next $ return True