2012-07-31 01:11:32 -04: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
|
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-08-26 15:39:02 -04:00
|
|
|
import Assistant.DaemonStatus
|
2012-08-31 15:17:12 -04:00
|
|
|
import Assistant.WebApp.Configurators.Local
|
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)
|
|
|
|
|
|
|
|
import Yesod
|
2012-07-31 21:06:30 -04:00
|
|
|
import Data.Text (Text)
|
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-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-08-03 20:40:34 -04:00
|
|
|
repolist <- lift repoList
|
2012-08-05 19:55:06 -04:00
|
|
|
$(widgetFile "configurators/repositories")
|
2012-08-03 20:40:34 -04:00
|
|
|
|
|
|
|
{- A numbered list of known repositories, including the current one. -}
|
|
|
|
repoList :: Handler [(String, String)]
|
2012-08-03 14:36:16 -04:00
|
|
|
repoList = do
|
2012-08-26 15:39:02 -04:00
|
|
|
rs <- filter (not . Remote.readonly) . knownRemotes <$>
|
|
|
|
(liftIO . getDaemonStatus =<< daemonStatus <$> getYesod)
|
2012-08-03 14:36:16 -04:00
|
|
|
l <- runAnnex [] $ do
|
2012-07-31 01:11:32 -04:00
|
|
|
u <- getUUID
|
2012-08-26 15:39:02 -04:00
|
|
|
Remote.prettyListUUIDs $ nub $ u:(map Remote.uuid rs)
|
2012-08-03 20:40:34 -04:00
|
|
|
return $ zip counter l
|
2012-07-31 01:11:32 -04:00
|
|
|
where
|
|
|
|
counter = map show ([1..] :: [Int])
|
2012-08-03 14:36:16 -04:00
|
|
|
|
|
|
|
{- An intro message, list of repositories, and nudge to make more. -}
|
|
|
|
introDisplay :: Text -> Widget
|
|
|
|
introDisplay ident = do
|
|
|
|
webapp <- lift getYesod
|
2012-08-03 20:40:34 -04:00
|
|
|
repolist <- lift repoList
|
|
|
|
let n = length repolist
|
|
|
|
let numrepos = show n
|
|
|
|
let notenough = n < enough
|
|
|
|
let barelyenough = n == enough
|
|
|
|
let morethanenough = n > enough
|
2012-08-03 14:36:16 -04:00
|
|
|
$(widgetFile "configurators/intro")
|
|
|
|
lift $ modifyWebAppState $ \s -> s { showIntro = False }
|
2012-08-03 20:40:34 -04:00
|
|
|
where
|
|
|
|
enough = 2
|