git-annex/Assistant/WebApp/Configurators.hs
Joey Hess 0b266f970f set/unset annex-sync, rather than annex-ignore
This reserves annex.ignore for repos that should not be visible at all;
repos with syncing disabled are now skipped by the assistant, but are
displayed in the list and can be configured.
2012-10-11 19:22:29 -04:00

116 lines
3.5 KiB
Haskell

{- git-annex assistant webapp configurators
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
module Assistant.WebApp.Configurators where
import Assistant.Common
import Assistant.WebApp
import Assistant.WebApp.Types
import Assistant.WebApp.SideBar
import Assistant.DaemonStatus
import Assistant.WebApp.Configurators.Local
import Utility.Yesod
import qualified Remote
import qualified Types.Remote as Remote
import Annex.UUID (getUUID)
import Logs.Remote
import Logs.Trust
import Config
import Yesod
import Data.Text (Text)
import qualified Data.Map as M
{- The main configuration screen. -}
getConfigR :: Handler RepHtml
getConfigR = ifM (inFirstRun)
( getFirstRepositoryR
, bootstrap (Just Config) $ do
sideBarDisplay
setTitle "Configuration"
$(widgetFile "configurators/main")
)
{- Lists known repositories, followed by options to add more. -}
getRepositoriesR :: Handler RepHtml
getRepositoriesR = bootstrap (Just Config) $ do
sideBarDisplay
setTitle "Repositories"
repolist <- lift $ repoList False True
$(widgetFile "configurators/repositories")
data SetupRepo =
EnableRepo (Route WebApp) |
EditRepo (Route WebApp) |
EnableSyncRepo (Route WebApp)
needsEnabled :: SetupRepo -> Bool
needsEnabled (EnableRepo _) = True
needsEnabled _ = False
notSyncing :: SetupRepo -> Bool
notSyncing (EnableSyncRepo _) = True
notSyncing _ = False
setupRepoLink :: SetupRepo -> Route WebApp
setupRepoLink (EnableRepo r) = r
setupRepoLink (EditRepo r) = r
setupRepoLink (EnableSyncRepo r) = r
{- A numbered list of known repositories. -}
repoList :: Bool -> Bool -> Handler [(String, String, SetupRepo)]
repoList onlyconfigured includehere
| onlyconfigured = list =<< configured
| otherwise = list =<< (++) <$> configured <*> rest
where
configured = do
rs <- filter (not . Remote.readonly) . knownRemotes <$>
(liftIO . getDaemonStatus =<< daemonStatus <$> getYesod)
runAnnex [] $ do
u <- getUUID
let l = map Remote.uuid rs
let l' = if includehere then u : l else l
return $ withlinks (EditRepo . EditRepositoryR) l'
withlinks mklink l = zip l (map mklink l)
rest = runAnnex [] $ do
m <- readRemoteLog
unconfigured <- catMaybes . map (findtype m) . snd
<$> (trustPartition DeadTrusted $ M.keys m)
unsyncable <- withlinks (EnableSyncRepo . EditRepositoryR) . map Remote.uuid <$>
(filterM (\r -> not <$> repoSyncable (Remote.repo r))
=<< Remote.enabledRemoteList)
return $ unsyncable ++ unconfigured
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
Just "S3" -> u `enableswith` EnableS3R
_ -> Nothing
u `enableswith` r = Just (u, EnableRepo $ r u)
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')
counter = map show ([1..] :: [Int])
{- 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