git-annex/Assistant/MakeRemote.hs

185 lines
6.7 KiB
Haskell
Raw Normal View History

2012-09-11 01:55:59 +00:00
{- git-annex assistant remote creation utilities
-
- Copyright 2012, 2013 Joey Hess <id@joeyh.name>
2012-09-11 01:55:59 +00:00
-
- Licensed under the GNU AGPL version 3 or higher.
2012-09-11 01:55:59 +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
import Remote.List.Util
2012-09-11 01:55:59 +00:00
import qualified Remote.Rsync as Rsync
import qualified Remote.GCrypt as GCrypt
2012-09-11 01:55:59 +00:00
import qualified Git
import qualified Git.Command
import qualified Annex
import qualified Annex.SpecialRemote
import Annex.SpecialRemote.Config
2012-09-11 01:55:59 +00:00
import Logs.UUID
import Logs.Remote
import Git.Remote
import Git.Types (RemoteName)
import Creds
import Assistant.Gpg
import Utility.Gpg (KeyId)
import Types.GitConfig
import Config
import Types.ProposedAccepted
2012-09-11 01:55:59 +00:00
import qualified Data.Map as M
{- 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
| onlyCapability sshdata RsyncCapable = makeRsyncRemote
2012-10-31 06:34:03 +00:00
| otherwise = makeGitRemote
2012-09-11 01:55:59 +00:00
{- Runs an action that returns a name of the remote, and finishes adding it. -}
addRemote :: Annex RemoteName -> Annex Remote
2012-09-11 01:55:59 +00:00
addRemote a = do
name <- a
remotesChanged
maybe (giveup "failed to add remote") return
=<< 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. -}
makeRsyncRemote :: RemoteName -> String -> Annex String
makeRsyncRemote name location = makeRemote name location $ const $ void $
go =<< Annex.SpecialRemote.findExisting name
2012-10-31 06:34:03 +00:00
where
go [] = setupSpecialRemote name Rsync.remote config Nothing
(Nothing, R.Init, Annex.SpecialRemote.newConfig name Nothing mempty mempty) Nothing
go ((u, c, mcu):_) = setupSpecialRemote name Rsync.remote config Nothing
(Just u, R.Enable c, c) mcu
2012-10-31 06:34:03 +00:00
config = M.fromList
[ (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
{- Inits a gcrypt special remote, and returns its name. -}
makeGCryptRemote :: RemoteName -> String -> KeyId -> Annex RemoteName
makeGCryptRemote remotename location keyid =
initSpecialRemote remotename GCrypt.remote Nothing $ M.fromList
[ (typeField, Proposed "gcrypt")
, (Proposed "gitrepo", Proposed location)
, configureEncryption HybridEncryption
, (Proposed "keyid", Proposed keyid)
]
type SpecialRemoteMaker = RemoteName -> RemoteType -> Maybe CredPair -> R.RemoteConfig -> Annex RemoteName
{- 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
initSpecialRemote name remotetype mcreds config = go 0
where
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
[] -> setupSpecialRemote fullname remotetype config mcreds
(Nothing, R.Init, Annex.SpecialRemote.newConfig fullname Nothing mempty mempty) Nothing
_ -> go (n + 1)
{- 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
[] -> giveup $ "Cannot find a special remote named " ++ name
((u, c, mcu):_) -> setupSpecialRemote' False name remotetype config mcreds (Just u, R.Enable c, c) mcu
setupSpecialRemote :: RemoteName -> RemoteType -> R.RemoteConfig -> Maybe CredPair -> (Maybe UUID, R.SetupStage, R.RemoteConfig) -> Maybe (Annex.SpecialRemote.ConfigFrom UUID) -> Annex RemoteName
setupSpecialRemote = setupSpecialRemote' True
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
{- 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. -}
let weakc = M.insert (Proposed "highRandomQuality") (Proposed "false") (M.union config c)
dummycfg <- liftIO dummyRemoteGitConfig
(c', u) <- R.setup remotetype ss mu mcreds weakc dummycfg
case mcu of
Nothing ->
configSet u c'
Just (Annex.SpecialRemote.ConfigFrom cu) -> do
setConfig (remoteAnnexConfig c' "config-uuid") (fromUUID cu)
configSet cu c'
when setdesc $
whenM (isNothing . M.lookup u <$> uuidDescMap) $
describeUUID u (toUUIDDesc name)
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. -}
makeGitRemote :: String -> String -> Annex RemoteName
2012-09-11 01:55:59 +00:00
makeGitRemote basename location = makeRemote basename location $ \name ->
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. -}
makeRemote :: String -> String -> (RemoteName -> Annex ()) -> Annex RemoteName
2012-09-11 01:55:59 +00:00
makeRemote basename location a = do
rs <- Annex.getGitRemotes
if not (any samelocation rs)
2012-09-11 01:55:59 +00:00
then do
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
{- 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. -}
uniqueRemoteName :: String -> Int -> [Git.Repo] -> RemoteName
uniqueRemoteName basename n rs
2012-09-11 01:55:59 +00:00
| null namecollision = name
| otherwise = uniqueRemoteName legalbasename (succ n) rs
2012-10-31 06:34:03 +00:00
where
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
legalbasename = makeLegalName basename
{- 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 =
getM fromstorage
=<< filter criteria . filter sametype
<$> Remote.remoteList
where
sametype r = R.typename (R.remotetype r) == R.typename remotetype
fromstorage r = do
let storage = getstorage (R.uuid r)
getRemoteCredPair (R.config r) (R.gitconfig r) storage