git-annex/Assistant/WebApp/Configurators.hs

92 lines
2.7 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 GPL 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
2012-07-31 05:11:32 +00:00
import Assistant.WebApp.SideBar
import Assistant.DaemonStatus
2012-08-31 19:17:12 +00:00
import Assistant.WebApp.Configurators.Local
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
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")
)
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
2012-08-05 23:55:06 +00:00
$(widgetFile "configurators/repositories")
2012-08-04 00:40:34 +00:00
{- A numbered list of known repositories, including the current one. -}
repoList :: Bool -> Handler [(String, String, Maybe (Route WebApp))]
repoList onlyconfigured
| onlyconfigured = list =<< configured
| otherwise = list =<< (++) <$> configured <*> unconfigured
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
return $ zip (u : map Remote.uuid rs) (repeat Nothing)
unconfigured = runAnnex [] $ do
m <- readRemoteLog
catMaybes . map (findtype m) . snd
<$> (trustPartition DeadTrusted $ M.keys m)
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
_ -> Nothing
u `enableswith` r = Just (u, Just $ 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])
{- An intro message, list of repositories, and nudge to make more. -}
introDisplay :: Text -> Widget
introDisplay ident = do
webapp <- lift getYesod
repolist <- lift $ repoList True
2012-08-04 00:40:34 +00:00
let n = length repolist
let numrepos = show n
let notenough = n < enough
let barelyenough = n == enough
let morethanenough = n > enough
$(widgetFile "configurators/intro")
lift $ modifyWebAppState $ \s -> s { showIntro = False }
2012-08-04 00:40:34 +00:00
where
enough = 2