2012-09-11 01:55:59 +00:00
|
|
|
{- git-annex assistant remote creation utilities
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2012, 2013 Joey Hess <id@joeyh.name>
|
2012-09-11 01:55:59 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2012-09-11 01:55:59 +00:00
|
|
|
-}
|
|
|
|
|
2019-12-05 19:10:23 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2012-09-11 01:55:59 +00:00
|
|
|
module Assistant.MakeRemote where
|
|
|
|
|
|
|
|
import Assistant.Common
|
|
|
|
import Assistant.Ssh
|
|
|
|
import qualified Types.Remote as R
|
|
|
|
import qualified Remote
|
2020-05-27 15:54:39 +00:00
|
|
|
import Remote.List.Util
|
2012-09-11 01:55:59 +00:00
|
|
|
import qualified Remote.Rsync as Rsync
|
2013-09-26 20:09:45 +00:00
|
|
|
import qualified Remote.GCrypt as GCrypt
|
2012-09-11 01:55:59 +00:00
|
|
|
import qualified Git
|
|
|
|
import qualified Git.Command
|
2018-01-09 19:36:56 +00:00
|
|
|
import qualified Annex
|
2015-09-14 18:49:48 +00:00
|
|
|
import qualified Annex.SpecialRemote
|
2019-10-10 19:46:12 +00:00
|
|
|
import Annex.SpecialRemote.Config
|
2012-09-11 01:55:59 +00:00
|
|
|
import Logs.UUID
|
|
|
|
import Logs.Remote
|
2012-10-31 19:17:00 +00:00
|
|
|
import Git.Remote
|
2013-11-07 22:02:00 +00:00
|
|
|
import Git.Types (RemoteName)
|
2013-04-27 19:16:06 +00:00
|
|
|
import Creds
|
2013-09-26 20:09:45 +00:00
|
|
|
import Assistant.Gpg
|
|
|
|
import Utility.Gpg (KeyId)
|
2017-08-17 16:26:14 +00:00
|
|
|
import Types.GitConfig
|
2019-10-11 18:59:41 +00:00
|
|
|
import Config
|
2020-01-10 18:10:20 +00:00
|
|
|
import Types.ProposedAccepted
|
2012-09-11 01:55:59 +00:00
|
|
|
|
|
|
|
import qualified Data.Map as M
|
|
|
|
|
2013-10-01 17:43:35 +00:00
|
|
|
{- Sets up a new git or rsync remote, accessed over ssh. -}
|
|
|
|
makeSshRemote :: SshData -> Annex RemoteName
|
2013-10-01 20:08:01 +00:00
|
|
|
makeSshRemote sshdata = maker (sshRepoName sshdata) (genSshUrl sshdata)
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
maker
|
2013-10-01 17:43:35 +00:00
|
|
|
| onlyCapability sshdata RsyncCapable = makeRsyncRemote
|
2012-10-31 06:34:03 +00:00
|
|
|
| otherwise = makeGitRemote
|
2013-09-26 20:09:45 +00:00
|
|
|
|
2012-09-11 01:55:59 +00:00
|
|
|
{- Runs an action that returns a name of the remote, and finishes adding it. -}
|
2013-07-20 21:52:14 +00:00
|
|
|
addRemote :: Annex RemoteName -> Annex Remote
|
2012-09-11 01:55:59 +00:00
|
|
|
addRemote a = do
|
|
|
|
name <- a
|
2020-05-27 15:54:39 +00:00
|
|
|
remotesChanged
|
2023-04-10 17:38:14 +00:00
|
|
|
maybe (giveup "failed to add remote") return
|
2013-03-05 19:39:42 +00:00
|
|
|
=<< Remote.byName (Just name)
|
2012-09-11 01:55:59 +00:00
|
|
|
|
2012-09-26 18:44:07 +00:00
|
|
|
{- Inits a rsync special remote, and returns its name. -}
|
2013-07-20 21:52:14 +00:00
|
|
|
makeRsyncRemote :: RemoteName -> String -> Annex String
|
|
|
|
makeRsyncRemote name location = makeRemote name location $ const $ void $
|
2015-09-14 18:49:48 +00:00
|
|
|
go =<< Annex.SpecialRemote.findExisting name
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
2022-01-05 19:24:02 +00:00
|
|
|
go [] = setupSpecialRemote name Rsync.remote config Nothing
|
2019-10-11 18:59:41 +00:00
|
|
|
(Nothing, R.Init, Annex.SpecialRemote.newConfig name Nothing mempty mempty) Nothing
|
2022-01-05 19:24:02 +00:00
|
|
|
go ((u, c, mcu):_) = setupSpecialRemote name Rsync.remote config Nothing
|
2019-10-11 18:59:41 +00:00
|
|
|
(Just u, R.Enable c, c) mcu
|
2012-10-31 06:34:03 +00:00
|
|
|
config = M.fromList
|
2020-01-10 18:10:20 +00:00
|
|
|
[ (encryptionField, Proposed "shared")
|
|
|
|
, (Proposed "rsyncurl", Proposed location)
|
|
|
|
, (typeField, Proposed "rsync")
|
2012-10-31 06:34:03 +00:00
|
|
|
]
|
2012-09-11 01:55:59 +00:00
|
|
|
|
2013-09-26 20:09:45 +00:00
|
|
|
{- Inits a gcrypt special remote, and returns its name. -}
|
|
|
|
makeGCryptRemote :: RemoteName -> String -> KeyId -> Annex RemoteName
|
|
|
|
makeGCryptRemote remotename location keyid =
|
2014-02-11 18:06:50 +00:00
|
|
|
initSpecialRemote remotename GCrypt.remote Nothing $ M.fromList
|
2020-01-10 18:10:20 +00:00
|
|
|
[ (typeField, Proposed "gcrypt")
|
|
|
|
, (Proposed "gitrepo", Proposed location)
|
2013-09-26 20:09:45 +00:00
|
|
|
, configureEncryption HybridEncryption
|
2020-01-10 18:10:20 +00:00
|
|
|
, (Proposed "keyid", Proposed keyid)
|
2013-09-26 20:09:45 +00:00
|
|
|
]
|
|
|
|
|
2014-02-11 18:06:50 +00:00
|
|
|
type SpecialRemoteMaker = RemoteName -> RemoteType -> Maybe CredPair -> R.RemoteConfig -> Annex RemoteName
|
2013-07-20 21:52:14 +00:00
|
|
|
|
|
|
|
{- Inits a new special remote. The name is used as a suggestion, but
|
|
|
|
- will be changed if there is already a special remote with that name. -}
|
|
|
|
initSpecialRemote :: SpecialRemoteMaker
|
2014-02-11 18:06:50 +00:00
|
|
|
initSpecialRemote name remotetype mcreds config = go 0
|
2013-04-26 22:22:44 +00:00
|
|
|
where
|
2013-07-20 21:52:14 +00:00
|
|
|
go :: Int -> Annex RemoteName
|
|
|
|
go n = do
|
|
|
|
let fullname = if n == 0 then name else name ++ show n
|
2017-12-05 19:00:50 +00:00
|
|
|
Annex.SpecialRemote.findExisting fullname >>= \case
|
2022-01-05 19:24:02 +00:00
|
|
|
[] -> setupSpecialRemote fullname remotetype config mcreds
|
2019-10-11 18:59:41 +00:00
|
|
|
(Nothing, R.Init, Annex.SpecialRemote.newConfig fullname Nothing mempty mempty) Nothing
|
2022-01-05 19:24:02 +00:00
|
|
|
_ -> go (n + 1)
|
2013-07-20 21:52:14 +00:00
|
|
|
|
|
|
|
{- Enables an existing special remote. -}
|
|
|
|
enableSpecialRemote :: SpecialRemoteMaker
|
2017-12-05 19:00:50 +00:00
|
|
|
enableSpecialRemote name remotetype mcreds config =
|
|
|
|
Annex.SpecialRemote.findExisting name >>= \case
|
2023-04-10 17:38:14 +00:00
|
|
|
[] -> giveup $ "Cannot find a special remote named " ++ name
|
2022-01-05 19:24:02 +00:00
|
|
|
((u, c, mcu):_) -> setupSpecialRemote' False name remotetype config mcreds (Just u, R.Enable c, c) mcu
|
2013-07-20 21:52:14 +00:00
|
|
|
|
2019-10-11 18:59:41 +00:00
|
|
|
setupSpecialRemote :: RemoteName -> RemoteType -> R.RemoteConfig -> Maybe CredPair -> (Maybe UUID, R.SetupStage, R.RemoteConfig) -> Maybe (Annex.SpecialRemote.ConfigFrom UUID) -> Annex RemoteName
|
2014-05-30 18:49:25 +00:00
|
|
|
setupSpecialRemote = setupSpecialRemote' True
|
|
|
|
|
2019-10-11 18:59:41 +00:00
|
|
|
setupSpecialRemote' :: Bool -> RemoteName -> RemoteType -> R.RemoteConfig -> Maybe CredPair -> (Maybe UUID, R.SetupStage, R.RemoteConfig) -> Maybe (Annex.SpecialRemote.ConfigFrom UUID) -> Annex RemoteName
|
|
|
|
setupSpecialRemote' setdesc name remotetype config mcreds (mu, ss, c) mcu = do
|
2013-07-20 21:52:14 +00:00
|
|
|
{- Currently, only 'weak' ciphers can be generated from the
|
|
|
|
- assistant, because otherwise GnuPG may block once the entropy
|
|
|
|
- pool is drained, and as of now there's no way to tell the user
|
|
|
|
- to perform IO actions to refill the pool. -}
|
2020-01-10 18:10:20 +00:00
|
|
|
let weakc = M.insert (Proposed "highRandomQuality") (Proposed "false") (M.union config c)
|
2017-08-17 16:26:14 +00:00
|
|
|
dummycfg <- liftIO dummyRemoteGitConfig
|
|
|
|
(c', u) <- R.setup remotetype ss mu mcreds weakc dummycfg
|
2019-10-11 18:59:41 +00:00
|
|
|
case mcu of
|
|
|
|
Nothing ->
|
|
|
|
configSet u c'
|
|
|
|
Just (Annex.SpecialRemote.ConfigFrom cu) -> do
|
2020-02-19 17:45:11 +00:00
|
|
|
setConfig (remoteAnnexConfig c' "config-uuid") (fromUUID cu)
|
2019-10-11 18:59:41 +00:00
|
|
|
configSet cu c'
|
2014-05-30 18:49:25 +00:00
|
|
|
when setdesc $
|
2019-01-01 19:39:45 +00:00
|
|
|
whenM (isNothing . M.lookup u <$> uuidDescMap) $
|
|
|
|
describeUUID u (toUUIDDesc name)
|
2013-07-20 21:52:14 +00:00
|
|
|
return name
|
2012-09-26 18:44:07 +00:00
|
|
|
|
2012-09-11 01:55:59 +00:00
|
|
|
{- Returns the name of the git remote it created. If there's already a
|
|
|
|
- remote at the location, returns its name. -}
|
2013-07-20 21:52:14 +00:00
|
|
|
makeGitRemote :: String -> String -> Annex RemoteName
|
2012-09-11 01:55:59 +00:00
|
|
|
makeGitRemote basename location = makeRemote basename location $ \name ->
|
2013-03-03 17:39:07 +00:00
|
|
|
void $ inRepo $ Git.Command.runBool
|
|
|
|
[Param "remote", Param "add", Param name, Param location]
|
2012-09-11 01:55:59 +00:00
|
|
|
|
|
|
|
{- If there's not already a remote at the location, adds it using the
|
|
|
|
- action, which is passed the name of the remote to make.
|
|
|
|
-
|
|
|
|
- Returns the name of the remote. -}
|
2013-07-20 21:52:14 +00:00
|
|
|
makeRemote :: String -> String -> (RemoteName -> Annex ()) -> Annex RemoteName
|
2012-09-11 01:55:59 +00:00
|
|
|
makeRemote basename location a = do
|
2018-01-09 19:36:56 +00:00
|
|
|
rs <- Annex.getGitRemotes
|
|
|
|
if not (any samelocation rs)
|
2012-09-11 01:55:59 +00:00
|
|
|
then do
|
2018-01-09 19:36:56 +00:00
|
|
|
let name = uniqueRemoteName basename 0 rs
|
2012-09-11 01:55:59 +00:00
|
|
|
a name
|
|
|
|
return name
|
|
|
|
else return basename
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
|
|
|
samelocation x = Git.repoLocation x == location
|
2012-09-11 01:55:59 +00:00
|
|
|
|
2018-01-09 19:36:56 +00:00
|
|
|
{- Given a list of all remotes, generate an unused name for a new
|
|
|
|
- remote, adding a number if necessary.
|
2012-09-29 16:27:43 +00:00
|
|
|
-
|
|
|
|
- Ensures that the returned name is a legal git remote name. -}
|
2018-01-09 19:36:56 +00:00
|
|
|
uniqueRemoteName :: String -> Int -> [Git.Repo] -> RemoteName
|
|
|
|
uniqueRemoteName basename n rs
|
2012-09-11 01:55:59 +00:00
|
|
|
| null namecollision = name
|
2018-01-09 19:36:56 +00:00
|
|
|
| otherwise = uniqueRemoteName legalbasename (succ n) rs
|
2012-10-31 06:34:03 +00:00
|
|
|
where
|
2018-01-09 19:36:56 +00:00
|
|
|
namecollision = filter samename rs
|
2012-10-31 06:34:03 +00:00
|
|
|
samename x = Git.remoteName x == Just name
|
|
|
|
name
|
|
|
|
| n == 0 = legalbasename
|
|
|
|
| otherwise = legalbasename ++ show n
|
2012-10-31 19:17:00 +00:00
|
|
|
legalbasename = makeLegalName basename
|
2013-04-27 19:16:06 +00:00
|
|
|
|
|
|
|
{- Finds a CredPair belonging to any Remote that is of a given type
|
|
|
|
- and matches some other criteria.
|
|
|
|
-
|
|
|
|
- This can be used as a default when another repository is being set up
|
|
|
|
- using the same service.
|
|
|
|
-
|
|
|
|
- A function must be provided that returns the CredPairStorage
|
|
|
|
- to use for a particular Remote's uuid.
|
|
|
|
-}
|
|
|
|
previouslyUsedCredPair
|
|
|
|
:: (UUID -> CredPairStorage)
|
|
|
|
-> RemoteType
|
|
|
|
-> (Remote -> Bool)
|
|
|
|
-> Annex (Maybe CredPair)
|
|
|
|
previouslyUsedCredPair getstorage remotetype criteria =
|
2020-05-27 15:54:39 +00:00
|
|
|
getM fromstorage
|
|
|
|
=<< filter criteria . filter sametype
|
|
|
|
<$> Remote.remoteList
|
2013-04-27 19:16:06 +00:00
|
|
|
where
|
|
|
|
sametype r = R.typename (R.remotetype r) == R.typename remotetype
|
|
|
|
fromstorage r = do
|
|
|
|
let storage = getstorage (R.uuid r)
|
2016-05-23 21:03:20 +00:00
|
|
|
getRemoteCredPair (R.config r) (R.gitconfig r) storage
|