summaryrefslogtreecommitdiff
path: root/Assistant/WebApp/Configurators.hs
blob: 6a467692a2e96fc3d1cd6dce2370b3ab1d0c6905 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
{- 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.SideBar
import Utility.Yesod
import qualified Remote
import Logs.Web (webUUID)
import Logs.Trust
import Annex.UUID (getUUID)

import Yesod
import Data.Text (Text, pack)

{- An intro message, list of repositories, and nudge to make more. -}
introDisplay :: Text -> Widget
introDisplay ident = do
	webapp <- lift getYesod
	l <- lift $ runAnnex [] $ do
		u <- getUUID
		rs <- map Remote.uuid <$> Remote.remoteList
		rs' <- snd <$> trustPartition DeadTrusted rs
		Remote.prettyListUUIDs $ filter (/= webUUID) $ nub $ u:rs'
	let remotelist = zip counter l
	let n = length l
	let numrepos = show n
	let notenough = n < 2
	let barelyenough = n == 2
	let morethanenough = n > 2
	$(widgetFile "configurators/intro")
	lift $ modifyWebAppState $ \s -> s { showIntro = False }
	where
		counter = map show ([1..] :: [Int])

data RepositoryPath = RepositoryPath Text
	deriving Show

addRepositoryForm :: Form RepositoryPath
addRepositoryForm msg = do
	cwd <- liftIO $ getCurrentDirectory
	(pathRes, pathView) <- mreq textField "" (Just $ pack cwd)
	let form = do
		webAppFormAuthToken
		$(widgetFile "configurators/addrepository/form")
	return (RepositoryPath <$> pathRes, form)

addRepository :: Bool -> Widget
addRepository firstrun = do
	setTitle $ if firstrun then "Getting started" else "Add repository"
	((res, form), enctype) <- lift $ runFormGet addRepositoryForm
	case res of
		FormSuccess (RepositoryPath p) -> error $ "TODO" ++ show p
		_ -> $(widgetFile "configurators/addrepository")

getAddRepositoryR :: Handler RepHtml
getAddRepositoryR = bootstrap (Just Config) $ do
	sideBarDisplay
	addRepository False

getConfigR :: Handler RepHtml
getConfigR = bootstrap (Just Config) $ do
	sideBarDisplay
	ifM (lift inFirstRun)
		( addRepository True
		, do
			setTitle "Configuration"
			$(widgetFile "configurators/main")
		)