2012-07-31 01:11:32 -04:00
|
|
|
{- git-annex assistant webapp configurators
|
|
|
|
-
|
|
|
|
- Copyright 2012 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
2012-09-24 14:48:47 -04:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2012-07-31 01:11:32 -04:00
|
|
|
-}
|
|
|
|
|
2012-10-18 16:14:49 +02:00
|
|
|
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes, CPP #-}
|
2012-07-31 01:11:32 -04:00
|
|
|
|
|
|
|
module Assistant.WebApp.Configurators where
|
|
|
|
|
|
|
|
import Assistant.Common
|
|
|
|
import Assistant.WebApp
|
2012-09-02 00:27:48 -04:00
|
|
|
import Assistant.WebApp.Types
|
2012-07-31 01:11:32 -04:00
|
|
|
import Assistant.WebApp.SideBar
|
2012-10-12 12:45:16 -04:00
|
|
|
import Assistant.WebApp.Utility
|
2012-08-31 15:17:12 -04:00
|
|
|
import Assistant.WebApp.Configurators.Local
|
2012-10-12 01:09:28 -04:00
|
|
|
import Assistant.DaemonStatus
|
2012-07-31 01:11:32 -04:00
|
|
|
import Utility.Yesod
|
|
|
|
import qualified Remote
|
2012-08-26 15:39:02 -04:00
|
|
|
import qualified Types.Remote as Remote
|
2012-07-31 01:11:32 -04:00
|
|
|
import Annex.UUID (getUUID)
|
2012-09-13 16:47:44 -04:00
|
|
|
import Logs.Remote
|
|
|
|
import Logs.Trust
|
2012-10-11 19:22:29 -04:00
|
|
|
import Config
|
2012-07-31 01:11:32 -04:00
|
|
|
|
|
|
|
import Yesod
|
2012-07-31 21:06:30 -04:00
|
|
|
import Data.Text (Text)
|
2012-09-13 16:47:44 -04:00
|
|
|
import qualified Data.Map as M
|
2012-07-31 01:11:32 -04:00
|
|
|
|
2012-08-03 14:36:16 -04:00
|
|
|
{- The main configuration screen. -}
|
|
|
|
getConfigR :: Handler RepHtml
|
|
|
|
getConfigR = ifM (inFirstRun)
|
|
|
|
( getFirstRepositoryR
|
|
|
|
, bootstrap (Just Config) $ do
|
2012-08-03 20:40:34 -04:00
|
|
|
sideBarDisplay
|
2012-08-03 14:36:16 -04:00
|
|
|
setTitle "Configuration"
|
|
|
|
$(widgetFile "configurators/main")
|
|
|
|
)
|
|
|
|
|
2012-10-12 01:09:28 -04:00
|
|
|
{- An intro message, list of repositories, and nudge to make more. -}
|
|
|
|
introDisplay :: Text -> Widget
|
|
|
|
introDisplay ident = do
|
|
|
|
webapp <- lift getYesod
|
|
|
|
repolist <- lift $ repoList True False
|
|
|
|
let n = length repolist
|
|
|
|
let numrepos = show n
|
|
|
|
let notenough = n < enough
|
|
|
|
$(widgetFile "configurators/intro")
|
|
|
|
lift $ modifyWebAppState $ \s -> s { showIntro = False }
|
|
|
|
where
|
|
|
|
enough = 2
|
|
|
|
|
2012-08-05 19:55:06 -04:00
|
|
|
{- Lists known repositories, followed by options to add more. -}
|
|
|
|
getRepositoriesR :: Handler RepHtml
|
|
|
|
getRepositoriesR = bootstrap (Just Config) $ do
|
2012-08-03 20:40:34 -04:00
|
|
|
sideBarDisplay
|
2012-08-05 19:55:06 -04:00
|
|
|
setTitle "Repositories"
|
2012-10-11 15:00:43 -04:00
|
|
|
repolist <- lift $ repoList False True
|
2012-08-05 19:55:06 -04:00
|
|
|
$(widgetFile "configurators/repositories")
|
2012-08-03 20:40:34 -04:00
|
|
|
|
2012-10-12 01:09:28 -04:00
|
|
|
data Actions
|
|
|
|
= DisabledRepoActions
|
|
|
|
{ setupRepoLink :: Route WebApp }
|
|
|
|
| SyncingRepoActions
|
|
|
|
{ setupRepoLink :: Route WebApp
|
|
|
|
, syncToggleLink :: Route WebApp
|
|
|
|
}
|
|
|
|
| NotSyncingRepoActions
|
|
|
|
{ setupRepoLink :: Route WebApp
|
|
|
|
, syncToggleLink :: Route WebApp
|
|
|
|
}
|
2012-10-09 14:43:53 -04:00
|
|
|
|
2012-10-12 01:09:28 -04:00
|
|
|
mkSyncingRepoActions :: UUID -> Actions
|
|
|
|
mkSyncingRepoActions u = SyncingRepoActions
|
|
|
|
{ setupRepoLink = EditRepositoryR u
|
|
|
|
, syncToggleLink = DisableSyncR u
|
|
|
|
}
|
2012-10-09 14:43:53 -04:00
|
|
|
|
2012-10-12 01:09:28 -04:00
|
|
|
mkNotSyncingRepoActions :: UUID -> Actions
|
|
|
|
mkNotSyncingRepoActions u = NotSyncingRepoActions
|
|
|
|
{ setupRepoLink = EditRepositoryR u
|
|
|
|
, syncToggleLink = EnableSyncR u
|
|
|
|
}
|
2012-10-11 19:22:29 -04:00
|
|
|
|
2012-10-12 01:09:28 -04:00
|
|
|
needsEnabled :: Actions -> Bool
|
|
|
|
needsEnabled (DisabledRepoActions _) = True
|
|
|
|
needsEnabled _ = False
|
|
|
|
|
|
|
|
notSyncing :: Actions -> Bool
|
|
|
|
notSyncing (SyncingRepoActions _ _) = False
|
|
|
|
notSyncing _ = True
|
2012-10-09 14:43:53 -04:00
|
|
|
|
2012-10-12 01:09:28 -04:00
|
|
|
{- A numbered list of known repositories,
|
|
|
|
- with actions that can be taken on them. -}
|
|
|
|
repoList :: Bool -> Bool -> Handler [(String, String, Actions)]
|
2012-10-11 15:00:43 -04:00
|
|
|
repoList onlyconfigured includehere
|
2012-09-13 16:47:44 -04:00
|
|
|
| onlyconfigured = list =<< configured
|
2012-10-11 19:22:29 -04:00
|
|
|
| otherwise = list =<< (++) <$> configured <*> rest
|
2012-07-31 01:11:32 -04:00
|
|
|
where
|
2012-09-13 16:47:44 -04:00
|
|
|
configured = do
|
2012-10-14 14:47:01 -04:00
|
|
|
rs <- filter (not . Remote.readonly) . syncRemotes <$>
|
2012-09-13 16:47:44 -04:00
|
|
|
(liftIO . getDaemonStatus =<< daemonStatus <$> getYesod)
|
|
|
|
runAnnex [] $ do
|
|
|
|
u <- getUUID
|
2012-10-11 15:00:43 -04:00
|
|
|
let l = map Remote.uuid rs
|
|
|
|
let l' = if includehere then u : l else l
|
2012-10-12 01:09:28 -04:00
|
|
|
return $ zip l' $ map mkSyncingRepoActions l'
|
2012-10-11 19:22:29 -04:00
|
|
|
rest = runAnnex [] $ do
|
2012-09-13 16:47:44 -04:00
|
|
|
m <- readRemoteLog
|
2012-10-11 19:22:29 -04:00
|
|
|
unconfigured <- catMaybes . map (findtype m) . snd
|
2012-09-13 16:47:44 -04:00
|
|
|
<$> (trustPartition DeadTrusted $ M.keys m)
|
2012-10-12 01:09:28 -04:00
|
|
|
unsyncable <- map Remote.uuid <$>
|
2012-10-11 19:22:29 -04:00
|
|
|
(filterM (\r -> not <$> repoSyncable (Remote.repo r))
|
|
|
|
=<< Remote.enabledRemoteList)
|
2012-10-12 01:09:28 -04:00
|
|
|
return $ zip unsyncable (map mkNotSyncingRepoActions unsyncable) ++ unconfigured
|
2012-09-13 16:47:44 -04:00
|
|
|
findtype m u = case M.lookup u m of
|
|
|
|
Nothing -> Nothing
|
|
|
|
Just c -> case M.lookup "type" c of
|
|
|
|
Just "rsync" -> u `enableswith` EnableRsyncR
|
|
|
|
Just "directory" -> u `enableswith` EnableDirectoryR
|
2012-10-18 16:14:49 +02:00
|
|
|
#ifdef WITH_S3
|
2012-09-26 15:24:23 -04:00
|
|
|
Just "S3" -> u `enableswith` EnableS3R
|
2012-10-18 16:14:49 +02:00
|
|
|
#endif
|
2012-09-13 16:47:44 -04:00
|
|
|
_ -> Nothing
|
2012-10-12 01:09:28 -04:00
|
|
|
u `enableswith` r = Just (u, DisabledRepoActions $ r u)
|
2012-09-13 16:47:44 -04:00
|
|
|
list l = runAnnex [] $ do
|
|
|
|
let l' = nubBy (\x y -> fst x == fst y) l
|
|
|
|
zip3
|
|
|
|
<$> pure counter
|
|
|
|
<*> Remote.prettyListUUIDs (map fst l')
|
|
|
|
<*> pure (map snd l')
|
2012-07-31 01:11:32 -04:00
|
|
|
counter = map show ([1..] :: [Int])
|
2012-08-03 14:36:16 -04:00
|
|
|
|
2012-10-12 01:09:28 -04:00
|
|
|
getEnableSyncR :: UUID -> Handler ()
|
2012-10-12 12:45:16 -04:00
|
|
|
getEnableSyncR = flipSync True
|
2012-10-12 01:09:28 -04:00
|
|
|
|
|
|
|
getDisableSyncR :: UUID -> Handler ()
|
2012-10-12 12:45:16 -04:00
|
|
|
getDisableSyncR = flipSync False
|
|
|
|
|
|
|
|
flipSync :: Bool -> UUID -> Handler ()
|
|
|
|
flipSync enable uuid = do
|
|
|
|
mremote <- runAnnex undefined $ snd <$> Remote.repoFromUUID uuid
|
|
|
|
changeSyncable mremote enable
|
2012-10-12 01:09:28 -04:00
|
|
|
redirect RepositoriesR
|