2013-03-13 01:51:03 +00:00
|
|
|
{- git-annex assistant webapp repository list
|
|
|
|
-
|
2013-03-15 02:10:51 +00:00
|
|
|
- Copyright 2012,2013 Joey Hess <joey@kitenet.net>
|
2013-03-13 01:51:03 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-06-05 01:02:09 +00:00
|
|
|
{-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings, CPP #-}
|
2013-03-13 01:51:03 +00:00
|
|
|
|
|
|
|
module Assistant.WebApp.RepoList where
|
|
|
|
|
|
|
|
import Assistant.WebApp.Common
|
|
|
|
import Assistant.DaemonStatus
|
|
|
|
import Assistant.WebApp.Notifications
|
|
|
|
import qualified Annex
|
|
|
|
import qualified Remote
|
|
|
|
import qualified Types.Remote as Remote
|
2013-03-13 21:59:33 +00:00
|
|
|
import Remote.List (remoteListRefresh)
|
2013-03-13 01:51:03 +00:00
|
|
|
import Annex.UUID (getUUID)
|
|
|
|
import Logs.Remote
|
|
|
|
import Logs.Trust
|
2013-04-04 01:58:08 +00:00
|
|
|
import Logs.Group
|
2013-03-13 21:59:33 +00:00
|
|
|
import Config
|
2013-09-26 21:26:13 +00:00
|
|
|
import Git.Remote
|
webapp: Improve handling of remotes whose setup has stalled.
This includes recovery from the ssh-agent problem that led to many reporting
http://git-annex.branchable.com/bugs/Internal_Server_Error:_Unknown_UUID/
(Including fixing up .ssh/config to set IdentitiesOnly.)
Remotes that have no known uuid are now displayed in the webapp as
"unfinished". There's a link to check their status, and if the remote
has been set annex-ignore, a retry button can be used to unset that and
try again to set up the remote.
As this bug has shown, the process of adding a ssh remote has some failure
modes that are not really ideal. It would certianly be better if, when
setting up a ssh remote it would detect if it's failed to get the UUID,
and handle that in the remote setup process, rather than waiting until
later and handling it this way.
However, that's hard to do, particularly for local pairing, since the
PairListener runs as a background thread. The best it could do is pop up an
alert if there's a problem. This solution is not much different.
Also, this solution handles cases where the user has gotten their repo into
a mess manually and let's the assistant help with cleaning it up.
This commit was sponsored by Chia Shee Liang. Thanks!
2013-07-31 20:01:20 +00:00
|
|
|
import Assistant.Sync
|
2013-03-13 21:59:33 +00:00
|
|
|
import Config.Cost
|
2013-09-27 04:35:37 +00:00
|
|
|
import Utility.NotificationBroadcaster
|
2013-03-13 01:51:03 +00:00
|
|
|
import qualified Git
|
|
|
|
|
|
|
|
import qualified Data.Map as M
|
2013-03-14 17:33:30 +00:00
|
|
|
import qualified Data.Set as S
|
2013-03-14 17:12:27 +00:00
|
|
|
import qualified Data.Text as T
|
2013-10-02 05:06:59 +00:00
|
|
|
import Data.Function
|
2014-03-06 22:11:44 +00:00
|
|
|
import Control.Concurrent
|
2013-03-13 01:51:03 +00:00
|
|
|
|
2014-04-09 19:26:41 +00:00
|
|
|
type RepoList = [(RepoDesc, RepoId, CurrentlyConnected, Actions)]
|
2013-11-07 22:02:00 +00:00
|
|
|
|
|
|
|
type RepoDesc = String
|
2014-04-09 19:26:41 +00:00
|
|
|
type CurrentlyConnected = Bool
|
2013-11-07 22:02:00 +00:00
|
|
|
|
|
|
|
{- Actions that can be performed on a repo in the list. -}
|
2013-03-13 01:51:03 +00:00
|
|
|
data Actions
|
|
|
|
= DisabledRepoActions
|
|
|
|
{ setupRepoLink :: Route WebApp }
|
|
|
|
| SyncingRepoActions
|
|
|
|
{ setupRepoLink :: Route WebApp
|
|
|
|
, syncToggleLink :: Route WebApp
|
|
|
|
}
|
|
|
|
| NotSyncingRepoActions
|
|
|
|
{ setupRepoLink :: Route WebApp
|
|
|
|
, syncToggleLink :: Route WebApp
|
|
|
|
}
|
2013-04-04 01:58:08 +00:00
|
|
|
| UnwantedRepoActions
|
|
|
|
{ setupRepoLink :: Route WebApp }
|
2013-03-13 01:51:03 +00:00
|
|
|
|
2013-11-07 22:02:00 +00:00
|
|
|
mkSyncingRepoActions :: RepoId -> Actions
|
|
|
|
mkSyncingRepoActions repoid = SyncingRepoActions
|
|
|
|
{ setupRepoLink = EditRepositoryR repoid
|
|
|
|
, syncToggleLink = DisableSyncR repoid
|
2013-03-13 01:51:03 +00:00
|
|
|
}
|
|
|
|
|
2013-11-07 22:02:00 +00:00
|
|
|
mkNotSyncingRepoActions :: RepoId -> Actions
|
|
|
|
mkNotSyncingRepoActions repoid = NotSyncingRepoActions
|
|
|
|
{ setupRepoLink = EditRepositoryR repoid
|
|
|
|
, syncToggleLink = EnableSyncR repoid
|
2013-03-13 01:51:03 +00:00
|
|
|
}
|
|
|
|
|
2013-11-07 22:02:00 +00:00
|
|
|
mkUnwantedRepoActions :: RepoId -> Actions
|
|
|
|
mkUnwantedRepoActions repoid = UnwantedRepoActions
|
|
|
|
{ setupRepoLink = EditRepositoryR repoid
|
2013-04-04 01:58:08 +00:00
|
|
|
}
|
|
|
|
|
2013-03-13 01:51:03 +00:00
|
|
|
needsEnabled :: Actions -> Bool
|
|
|
|
needsEnabled (DisabledRepoActions _) = True
|
|
|
|
needsEnabled _ = False
|
|
|
|
|
|
|
|
notSyncing :: Actions -> Bool
|
2013-03-14 15:55:36 +00:00
|
|
|
notSyncing (SyncingRepoActions _ _) = False
|
2013-03-13 01:51:03 +00:00
|
|
|
notSyncing _ = True
|
|
|
|
|
2013-04-04 01:58:08 +00:00
|
|
|
notWanted :: Actions -> Bool
|
|
|
|
notWanted (UnwantedRepoActions _) = True
|
|
|
|
notWanted _ = False
|
|
|
|
|
2013-03-13 01:51:03 +00:00
|
|
|
{- Called by client to get a list of repos, that refreshes
|
2013-03-15 04:34:42 +00:00
|
|
|
- when new repos are added.
|
2013-03-13 01:51:03 +00:00
|
|
|
-
|
|
|
|
- Returns a div, which will be inserted into the calling page.
|
|
|
|
-}
|
2013-09-27 04:35:37 +00:00
|
|
|
getRepoListR :: NotificationId -> RepoSelector -> Handler Html
|
|
|
|
getRepoListR nid reposelector = do
|
2013-03-13 01:51:03 +00:00
|
|
|
waitNotifier getRepoListBroadcaster nid
|
|
|
|
p <- widgetToPageContent $ repoListDisplay reposelector
|
2013-06-27 05:15:28 +00:00
|
|
|
giveUrlRenderer $ [hamlet|^{pageBody p}|]
|
2013-03-13 01:51:03 +00:00
|
|
|
|
2013-03-15 04:34:42 +00:00
|
|
|
mainRepoSelector :: RepoSelector
|
|
|
|
mainRepoSelector = RepoSelector
|
|
|
|
{ onlyCloud = False
|
|
|
|
, onlyConfigured = False
|
|
|
|
, includeHere = True
|
|
|
|
, nudgeAddMore = False
|
|
|
|
}
|
|
|
|
|
2013-03-15 21:52:41 +00:00
|
|
|
{- List of cloud repositories, configured and not. -}
|
|
|
|
cloudRepoList :: Widget
|
2013-10-02 05:06:59 +00:00
|
|
|
cloudRepoList = repoListDisplay RepoSelector
|
2013-03-15 21:52:41 +00:00
|
|
|
{ onlyCloud = True
|
|
|
|
, onlyConfigured = False
|
|
|
|
, includeHere = False
|
|
|
|
, nudgeAddMore = False
|
|
|
|
}
|
|
|
|
|
2013-03-13 01:51:03 +00:00
|
|
|
repoListDisplay :: RepoSelector -> Widget
|
|
|
|
repoListDisplay reposelector = do
|
|
|
|
autoUpdate ident (NotifierRepoListR reposelector) (10 :: Int) (10 :: Int)
|
2014-04-07 17:37:03 +00:00
|
|
|
addScript $ StaticR js_jquery_ui_core_js
|
|
|
|
addScript $ StaticR js_jquery_ui_widget_js
|
|
|
|
addScript $ StaticR js_jquery_ui_mouse_js
|
|
|
|
addScript $ StaticR js_jquery_ui_sortable_js
|
2013-03-13 01:51:03 +00:00
|
|
|
|
2013-06-03 17:51:54 +00:00
|
|
|
repolist <- liftH $ repoList reposelector
|
2013-03-15 04:34:42 +00:00
|
|
|
let addmore = nudgeAddMore reposelector
|
|
|
|
let nootherrepos = length repolist < 2
|
2013-03-13 01:51:03 +00:00
|
|
|
|
2013-03-15 02:10:51 +00:00
|
|
|
$(widgetFile "repolist")
|
2013-03-13 01:51:03 +00:00
|
|
|
where
|
|
|
|
ident = "repolist"
|
|
|
|
|
2013-03-15 04:34:42 +00:00
|
|
|
{- A list of known repositories, with actions that can be taken on them. -}
|
2013-03-13 01:51:03 +00:00
|
|
|
repoList :: RepoSelector -> Handler RepoList
|
|
|
|
repoList reposelector
|
|
|
|
| onlyConfigured reposelector = list =<< configured
|
2013-03-14 17:33:30 +00:00
|
|
|
| otherwise = list =<< (++) <$> configured <*> unconfigured
|
2013-03-13 01:51:03 +00:00
|
|
|
where
|
|
|
|
configured = do
|
2013-11-07 22:02:00 +00:00
|
|
|
syncremotes <- syncRemotes <$> liftAssistant getDaemonStatus
|
|
|
|
let syncing = S.fromList $ map mkRepoId syncremotes
|
2013-03-13 01:51:03 +00:00
|
|
|
liftAnnex $ do
|
2013-04-04 01:58:08 +00:00
|
|
|
unwanted <- S.fromList
|
2013-11-07 22:02:00 +00:00
|
|
|
<$> filterM inUnwantedGroup (map Remote.uuid syncremotes)
|
2013-04-04 01:58:08 +00:00
|
|
|
rs <- filter selectedrepo . concat . Remote.byCost
|
2013-04-22 18:57:09 +00:00
|
|
|
<$> Remote.remoteList
|
2013-11-07 22:02:00 +00:00
|
|
|
let l = flip map (map mkRepoId rs) $ \r -> case r of
|
|
|
|
(RepoUUID u)
|
|
|
|
| u `S.member` unwanted -> (r, mkUnwantedRepoActions r)
|
|
|
|
_
|
|
|
|
| r `S.member` syncing -> (r, mkSyncingRepoActions r)
|
|
|
|
| otherwise -> (r, mkNotSyncingRepoActions r)
|
2013-03-13 01:51:03 +00:00
|
|
|
if includeHere reposelector
|
|
|
|
then do
|
2013-11-07 22:02:00 +00:00
|
|
|
r <- RepoUUID <$> getUUID
|
2013-03-13 01:51:03 +00:00
|
|
|
autocommit <- annexAutoCommit <$> Annex.getGitConfig
|
|
|
|
let hereactions = if autocommit
|
2013-11-07 22:02:00 +00:00
|
|
|
then mkSyncingRepoActions r
|
|
|
|
else mkNotSyncingRepoActions r
|
|
|
|
let here = (r, hereactions)
|
2013-03-13 01:51:03 +00:00
|
|
|
return $ here : l
|
|
|
|
else return l
|
2013-03-14 17:33:30 +00:00
|
|
|
unconfigured = liftAnnex $ do
|
2013-03-13 01:51:03 +00:00
|
|
|
m <- readRemoteLog
|
2013-09-26 21:26:13 +00:00
|
|
|
g <- gitRepo
|
2013-04-04 01:58:08 +00:00
|
|
|
map snd . catMaybes . filter selectedremote
|
2013-09-26 21:26:13 +00:00
|
|
|
. map (findinfo m g)
|
2013-10-02 05:06:59 +00:00
|
|
|
<$> trustExclude DeadTrusted (M.keys m)
|
2013-04-04 01:58:08 +00:00
|
|
|
selectedrepo r
|
2013-03-13 01:51:03 +00:00
|
|
|
| Remote.readonly r = False
|
2013-11-07 22:02:00 +00:00
|
|
|
| onlyCloud reposelector = Git.repoIsUrl (Remote.repo r)
|
|
|
|
&& Remote.uuid r /= NoUUID
|
2014-02-01 14:33:55 +00:00
|
|
|
&& not (Remote.isXMPPRemote r)
|
2013-03-13 01:51:03 +00:00
|
|
|
| otherwise = True
|
2013-04-04 01:58:08 +00:00
|
|
|
selectedremote Nothing = False
|
|
|
|
selectedremote (Just (iscloud, _))
|
2013-03-13 01:51:03 +00:00
|
|
|
| onlyCloud reposelector = iscloud
|
|
|
|
| otherwise = True
|
2013-09-26 21:26:13 +00:00
|
|
|
findinfo m g u = case getconfig "type" of
|
2013-04-25 20:42:17 +00:00
|
|
|
Just "rsync" -> val True EnableRsyncR
|
|
|
|
Just "directory" -> val False EnableDirectoryR
|
2013-03-13 01:51:03 +00:00
|
|
|
#ifdef WITH_S3
|
2013-04-25 20:42:17 +00:00
|
|
|
Just "S3" -> val True EnableS3R
|
2013-03-13 01:51:03 +00:00
|
|
|
#endif
|
2013-04-25 20:42:17 +00:00
|
|
|
Just "glacier" -> val True EnableGlacierR
|
2013-03-13 01:51:03 +00:00
|
|
|
#ifdef WITH_WEBDAV
|
2013-04-25 20:42:17 +00:00
|
|
|
Just "webdav" -> val True EnableWebDAVR
|
2013-03-13 01:51:03 +00:00
|
|
|
#endif
|
2013-09-26 21:26:13 +00:00
|
|
|
Just "gcrypt" ->
|
|
|
|
-- Skip gcrypt repos on removable drives;
|
|
|
|
-- handled separately.
|
|
|
|
case getconfig "gitrepo" of
|
|
|
|
Just rr | remoteLocationIsUrl (parseRemoteLocation rr g) ->
|
2013-10-02 19:54:32 +00:00
|
|
|
val True EnableSshGCryptR
|
2013-09-26 21:26:13 +00:00
|
|
|
_ -> Nothing
|
2013-04-25 20:42:17 +00:00
|
|
|
_ -> Nothing
|
2013-03-13 01:51:03 +00:00
|
|
|
where
|
2013-09-26 21:26:13 +00:00
|
|
|
getconfig k = M.lookup k =<< M.lookup u m
|
2013-11-07 22:02:00 +00:00
|
|
|
val iscloud r = Just (iscloud, (RepoUUID u, DisabledRepoActions $ r u))
|
2014-04-09 19:26:41 +00:00
|
|
|
list l = do
|
|
|
|
cc <- currentlyConnectedRemotes <$> liftAssistant getDaemonStatus
|
2013-11-07 22:02:00 +00:00
|
|
|
forM (nubBy ((==) `on` fst) l) $ \(repoid, actions) ->
|
2014-04-09 19:26:41 +00:00
|
|
|
(,,,)
|
|
|
|
<$> liftAnnex (describeRepoId repoid)
|
2013-11-07 22:02:00 +00:00
|
|
|
<*> pure repoid
|
2014-04-09 19:26:41 +00:00
|
|
|
<*> pure (getCurrentlyConnected repoid cc)
|
2013-11-07 22:02:00 +00:00
|
|
|
<*> pure actions
|
|
|
|
|
2014-04-09 19:26:41 +00:00
|
|
|
getCurrentlyConnected :: RepoId -> S.Set UUID -> CurrentlyConnected
|
|
|
|
getCurrentlyConnected (RepoUUID u) cc = S.member u cc
|
|
|
|
getCurrentlyConnected _ _ = False
|
|
|
|
|
2013-11-07 22:02:00 +00:00
|
|
|
getEnableSyncR :: RepoId -> Handler ()
|
2013-03-13 01:51:03 +00:00
|
|
|
getEnableSyncR = flipSync True
|
|
|
|
|
2013-11-07 22:02:00 +00:00
|
|
|
getDisableSyncR :: RepoId -> Handler ()
|
2013-03-13 01:51:03 +00:00
|
|
|
getDisableSyncR = flipSync False
|
|
|
|
|
2013-11-07 22:02:00 +00:00
|
|
|
flipSync :: Bool -> RepoId -> Handler ()
|
|
|
|
flipSync enable repoid = do
|
|
|
|
mremote <- liftAnnex $ repoIdRemote repoid
|
2013-10-26 20:54:49 +00:00
|
|
|
liftAssistant $ changeSyncable mremote enable
|
2013-03-15 04:34:42 +00:00
|
|
|
redirectBack
|
2013-03-13 21:59:33 +00:00
|
|
|
|
2013-03-14 15:55:36 +00:00
|
|
|
getRepositoriesReorderR :: Handler ()
|
|
|
|
getRepositoriesReorderR = do
|
2013-03-14 17:12:27 +00:00
|
|
|
{- Get uuid of the moved item, and the list it was moved within. -}
|
|
|
|
moved <- fromjs <$> runInputGet (ireq textField "moved")
|
|
|
|
list <- map fromjs <$> lookupGetParams "list[]"
|
2014-05-16 02:01:32 +00:00
|
|
|
liftAnnex $ go list =<< repoIdRemote moved
|
2013-03-18 17:13:33 +00:00
|
|
|
liftAssistant updateSyncRemotes
|
|
|
|
where
|
|
|
|
go _ Nothing = noop
|
|
|
|
go list (Just remote) = do
|
2014-05-16 02:01:32 +00:00
|
|
|
rs <- catMaybes <$> mapM repoIdRemote list
|
2013-03-14 19:23:45 +00:00
|
|
|
forM_ (reorderCosts remote rs) $ \(r, newcost) ->
|
2013-03-14 17:12:27 +00:00
|
|
|
when (Remote.cost r /= newcost) $
|
external special remotes mostly implemented (untested)
This has not been tested at all. It compiles!
The only known missing things are support for encryption, and for get/set
of special remote configuration, and of key state. (The latter needs
separate work to add a new per-key log file to store that state.)
Only thing I don't much like is that initremote needs to be passed both
type=external and externaltype=foo. It would be better to have just
type=foo
Most of this is quite straightforward code, that largely wrote itself given
the types. The only tricky parts were:
* Need to lock the remote when using it to eg make a request, because
in theory git-annex could have multiple threads that each try to use
a remote at the same time. I don't think that git-annex ever does
that currently, but better safe than sorry.
* Rather than starting up every external special remote program when
git-annex starts, they are started only on demand, when first used.
This will avoid slowdown, especially when running fast git-annex query
commands. Once started, they keep running until git-annex stops, currently,
which may not be ideal, but it's hard to know a better time to stop them.
* Bit of a chicken and egg problem with caching the cost of the remote,
because setting annex-cost in the git config needs the remote to already
be set up. Managed to finesse that.
This commit was sponsored by Lukas Anzinger.
2013-12-26 22:23:13 +00:00
|
|
|
setRemoteCost (Remote.repo r) newcost
|
2013-03-18 17:13:33 +00:00
|
|
|
void remoteListRefresh
|
2014-05-16 02:01:32 +00:00
|
|
|
fromjs = fromMaybe (RepoUUID NoUUID) . readish . T.unpack
|
2013-03-14 17:12:27 +00:00
|
|
|
|
2013-03-14 19:23:45 +00:00
|
|
|
reorderCosts :: Remote -> [Remote] -> [(Remote, Cost)]
|
|
|
|
reorderCosts remote rs = zip rs'' (insertCostAfter costs i)
|
2013-03-14 17:12:27 +00:00
|
|
|
where
|
2013-03-14 19:23:45 +00:00
|
|
|
{- Find the index of the remote in the list that the remote
|
2013-03-14 17:12:27 +00:00
|
|
|
- was moved to be after.
|
|
|
|
- If it was moved to the start of the list, -1 -}
|
2013-03-14 19:23:45 +00:00
|
|
|
i = fromMaybe 0 (elemIndex remote rs) - 1
|
|
|
|
rs' = filter (\r -> Remote.uuid r /= Remote.uuid remote) rs
|
2013-03-14 17:12:27 +00:00
|
|
|
costs = map Remote.cost rs'
|
|
|
|
rs'' = (\(x, y) -> x ++ [remote] ++ y) $ splitAt (i + 1) rs'
|
webapp: Improve handling of remotes whose setup has stalled.
This includes recovery from the ssh-agent problem that led to many reporting
http://git-annex.branchable.com/bugs/Internal_Server_Error:_Unknown_UUID/
(Including fixing up .ssh/config to set IdentitiesOnly.)
Remotes that have no known uuid are now displayed in the webapp as
"unfinished". There's a link to check their status, and if the remote
has been set annex-ignore, a retry button can be used to unset that and
try again to set up the remote.
As this bug has shown, the process of adding a ssh remote has some failure
modes that are not really ideal. It would certianly be better if, when
setting up a ssh remote it would detect if it's failed to get the UUID,
and handle that in the remote setup process, rather than waiting until
later and handling it this way.
However, that's hard to do, particularly for local pairing, since the
PairListener runs as a background thread. The best it could do is pop up an
alert if there's a problem. This solution is not much different.
Also, this solution handles cases where the user has gotten their repo into
a mess manually and let's the assistant help with cleaning it up.
This commit was sponsored by Chia Shee Liang. Thanks!
2013-07-31 20:01:20 +00:00
|
|
|
|
2014-03-06 22:11:44 +00:00
|
|
|
getSyncNowRepositoryR :: UUID -> Handler ()
|
|
|
|
getSyncNowRepositoryR uuid = do
|
|
|
|
u <- liftAnnex getUUID
|
|
|
|
if u == uuid
|
|
|
|
then do
|
|
|
|
thread <- liftAssistant $ asIO $
|
|
|
|
reconnectRemotes True
|
|
|
|
=<< (syncRemotes <$> getDaemonStatus)
|
|
|
|
void $ liftIO $ forkIO thread
|
|
|
|
else maybe noop (liftAssistant . syncRemote)
|
|
|
|
=<< liftAnnex (Remote.remoteFromUUID uuid)
|
|
|
|
redirectBack
|