git-annex/Assistant/WebApp/Configurators.hs

144 lines
4.2 KiB
Haskell
Raw Normal View History

2012-07-31 05:11:32 +00:00
{- git-annex assistant webapp configurators
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
2012-07-31 05:11:32 +00:00
-}
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
module Assistant.WebApp.Configurators where
import Assistant.Common
import Assistant.WebApp
import Assistant.WebApp.Types
2012-07-31 05:11:32 +00:00
import Assistant.WebApp.SideBar
import Assistant.WebApp.Utility
2012-08-31 19:17:12 +00:00
import Assistant.WebApp.Configurators.Local
import Assistant.DaemonStatus
2012-07-31 05:11:32 +00:00
import Utility.Yesod
import qualified Remote
import qualified Types.Remote as Remote
2012-07-31 05:11:32 +00:00
import Annex.UUID (getUUID)
import Logs.Remote
import Logs.Trust
import Config
2012-07-31 05:11:32 +00:00
import Yesod
import Data.Text (Text)
import qualified Data.Map as M
2012-07-31 05:11:32 +00:00
{- The main configuration screen. -}
getConfigR :: Handler RepHtml
getConfigR = ifM (inFirstRun)
( getFirstRepositoryR
, bootstrap (Just Config) $ do
2012-08-04 00:40:34 +00:00
sideBarDisplay
setTitle "Configuration"
$(widgetFile "configurators/main")
)
{- 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 23:55:06 +00:00
{- Lists known repositories, followed by options to add more. -}
getRepositoriesR :: Handler RepHtml
getRepositoriesR = bootstrap (Just Config) $ do
2012-08-04 00:40:34 +00:00
sideBarDisplay
2012-08-05 23:55:06 +00:00
setTitle "Repositories"
repolist <- lift $ repoList False True
2012-08-05 23:55:06 +00:00
$(widgetFile "configurators/repositories")
2012-08-04 00:40:34 +00:00
data Actions
= DisabledRepoActions
{ setupRepoLink :: Route WebApp }
| SyncingRepoActions
{ setupRepoLink :: Route WebApp
, syncToggleLink :: Route WebApp
}
| NotSyncingRepoActions
{ setupRepoLink :: Route WebApp
, syncToggleLink :: Route WebApp
}
mkSyncingRepoActions :: UUID -> Actions
mkSyncingRepoActions u = SyncingRepoActions
{ setupRepoLink = EditRepositoryR u
, syncToggleLink = DisableSyncR u
}
mkNotSyncingRepoActions :: UUID -> Actions
mkNotSyncingRepoActions u = NotSyncingRepoActions
{ setupRepoLink = EditRepositoryR u
, syncToggleLink = EnableSyncR u
}
needsEnabled :: Actions -> Bool
needsEnabled (DisabledRepoActions _) = True
needsEnabled _ = False
notSyncing :: Actions -> Bool
notSyncing (SyncingRepoActions _ _) = False
notSyncing _ = True
{- A numbered list of known repositories,
- with actions that can be taken on them. -}
repoList :: Bool -> Bool -> Handler [(String, String, Actions)]
repoList onlyconfigured includehere
| onlyconfigured = list =<< configured
| otherwise = list =<< (++) <$> configured <*> rest
2012-07-31 05:11:32 +00:00
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 $ zip l' $ map mkSyncingRepoActions l'
rest = runAnnex [] $ do
m <- readRemoteLog
unconfigured <- catMaybes . map (findtype m) . snd
<$> (trustPartition DeadTrusted $ M.keys m)
unsyncable <- map Remote.uuid <$>
(filterM (\r -> not <$> repoSyncable (Remote.repo r))
=<< Remote.enabledRemoteList)
return $ zip unsyncable (map mkNotSyncingRepoActions 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
2012-09-26 19:24:23 +00:00
Just "S3" -> u `enableswith` EnableS3R
_ -> Nothing
u `enableswith` r = Just (u, DisabledRepoActions $ 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')
2012-07-31 05:11:32 +00:00
counter = map show ([1..] :: [Int])
getEnableSyncR :: UUID -> Handler ()
getEnableSyncR = flipSync True
getDisableSyncR :: UUID -> Handler ()
getDisableSyncR = flipSync False
flipSync :: Bool -> UUID -> Handler ()
flipSync enable uuid = do
mremote <- runAnnex undefined $ snd <$> Remote.repoFromUUID uuid
changeSyncable mremote enable
redirect RepositoriesR