This commit is contained in:
Joey Hess 2012-11-25 00:38:11 -04:00
parent 59733456ed
commit 3dfc9cadb0
20 changed files with 28 additions and 49 deletions

View file

@ -11,13 +11,11 @@ module Assistant.WebApp where
import Assistant.WebApp.Types
import Assistant.Common
import Assistant.Alert
import Utility.NotificationBroadcaster
import Utility.Yesod
import Locations.UserConfig
import Yesod
import Text.Hamlet
import Data.Text (Text)
import Control.Concurrent.STM
import Control.Concurrent
@ -115,14 +113,3 @@ listOtherRepos = do
dirs <- nub <$> ifM (doesFileExist f) ( lines <$> readFile f, return [])
names <- mapM relHome dirs
return $ sort $ zip names dirs
htmlIcon :: AlertIcon -> GWidget sub master ()
htmlIcon ActivityIcon = bootstrapIcon "refresh"
htmlIcon InfoIcon = bootstrapIcon "info-sign"
htmlIcon SuccessIcon = bootstrapIcon "ok"
htmlIcon ErrorIcon = bootstrapIcon "exclamation-sign"
-- utf-8 umbrella (utf-8 cloud looks too stormy)
htmlIcon TheCloud = [whamlet|&#9730;|]
bootstrapIcon :: Text -> GWidget sub master ()
bootstrapIcon name = [whamlet|<i .icon-#{name}></i>|]

View file

@ -102,9 +102,7 @@ getAddS3R = awsConfigurator $ do
, ("datacenter", T.unpack $ datacenter input)
, ("storageclass", show $ storageClass input)
]
_ -> do
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/adds3")
_ -> $(widgetFile "configurators/adds3")
where
setgroup r = runAnnex () $
setStandardGroup (Remote.uuid r) TransferGroup
@ -124,9 +122,7 @@ getAddGlacierR = glacierConfigurator $ do
, ("type", "glacier")
, ("datacenter", T.unpack $ datacenter input)
]
_ -> do
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/addglacier")
_ -> $(widgetFile "configurators/addglacier")
where
setgroup r = runAnnex () $
setStandardGroup (Remote.uuid r) SmallArchiveGroup
@ -152,7 +148,6 @@ enableAWSRemote remotetype uuid = do
fromJust $ M.lookup uuid m
makeAWSRemote remotetype creds name (const noop) M.empty
_ -> do
let authtoken = webAppFormAuthToken
description <- lift $ runAnnex "" $
T.pack . concat <$> Remote.prettyListUUIDs [uuid]
$(widgetFile "configurators/enableaws")

View file

@ -126,7 +126,6 @@ editForm new uuid = page "Configure repository" (Just Config) $ do
where
showform form enctype curr = do
let istransfer = repoGroup curr == RepoGroupStandard TransferGroup
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/editrepository")
{- Makes a toplevel archive directory, so the user can get on with

View file

@ -184,9 +184,7 @@ getAddDriveR = page "AAdd a removable drive" (Just Config) $ do
case res of
FormSuccess (RemovableDrive { mountPoint = d }) -> lift $
make (T.unpack d) >>= redirect . EditNewRepositoryR
_ -> do
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/adddrive")
_ -> $(widgetFile "configurators/adddrive")
where
make mountpoint = do
liftIO $ makerepo dir

View file

@ -259,7 +259,6 @@ promptSecret msg cont = pairPage $ do
(verifiableVal . fromPairMsg <$> msg)
u <- T.pack <$> liftIO myUserName
let sameusername = username == u
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/pairing/local/prompt")
{- This counts unicode characters as more than one character,

View file

@ -100,9 +100,7 @@ getAddSshR = sshConfigurator $ do
Right sshdata -> lift $ redirect $ ConfirmSshR sshdata
_ -> showform form enctype UntestedServer
where
showform form enctype status = do
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/ssh/add")
showform form enctype status = $(widgetFile "configurators/ssh/add")
{- To enable an existing rsync special remote, parse the SshInput from
- its rsyncurl, and display a form whose only real purpose is to check
@ -135,7 +133,6 @@ getEnableRsyncR u = do
showform form enctype status = do
description <- lift $ runAnnex "" $
T.pack . concat <$> prettyListUUIDs [u]
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/ssh/enable")
enable sshdata = lift $ redirect $ ConfirmSshR $
sshdata { rsyncOnly = True }
@ -237,8 +234,7 @@ showSshErr msg = sshConfigurator $
$(widgetFile "configurators/ssh/error")
getConfirmSshR :: SshData -> Handler RepHtml
getConfirmSshR sshdata = sshConfigurator $ do
let authtoken = webAppFormAuthToken
getConfirmSshR sshdata = sshConfigurator $
$(widgetFile "configurators/ssh/confirm")
getMakeSshGitR :: SshData -> Handler RepHtml

View file

@ -62,9 +62,7 @@ getAddBoxComR = boxConfigurator $ do
-- performance.
, ("chunksize", "10mb")
]
_ -> do
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/addbox.com")
_ -> $(widgetFile "configurators/addbox.com")
where
setgroup r = runAnnex () $
setStandardGroup (Remote.uuid r) TransferGroup
@ -88,7 +86,6 @@ getEnableWebDAVR uuid = do
FormSuccess creds -> lift $
makeWebDavRemote name creds (const noop) M.empty
_ -> do
let authtoken = webAppFormAuthToken
description <- lift $ runAnnex "" $
T.pack . concat <$> Remote.prettyListUUIDs [uuid]
$(widgetFile "configurators/enablewebdav")

View file

@ -70,9 +70,7 @@ getXMPPR' redirto = xmppPage $ do
oldcreds <- runAnnex Nothing getXMPPCreds
runFormGet $ renderBootstrap $ xmppAForm $
creds2Form <$> oldcreds
let showform problem = do
let authtoken = webAppFormAuthToken
$(widgetFile "configurators/xmpp")
let showform problem = $(widgetFile "configurators/xmpp")
case result of
FormSuccess f -> either (showform . Just . show) (lift . storecreds)
=<< liftIO (validateForm f)

View file

@ -88,3 +88,13 @@ getClickAlert i = do
redirect $ buttonUrl b
_ -> redirectBack
htmlIcon :: AlertIcon -> GWidget sub master ()
htmlIcon ActivityIcon = bootstrapIcon "refresh"
htmlIcon InfoIcon = bootstrapIcon "info-sign"
htmlIcon SuccessIcon = bootstrapIcon "ok"
htmlIcon ErrorIcon = bootstrapIcon "exclamation-sign"
-- utf-8 umbrella (utf-8 cloud looks too stormy)
htmlIcon TheCloud = [whamlet|&#9730;|]
bootstrapIcon :: Text -> GWidget sub master ()
bootstrapIcon name = [whamlet|<i .icon-#{name}></i>|]

View file

@ -13,7 +13,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit onclick="$('#workingmodal').modal('show');">
Add repository

View file

@ -25,7 +25,7 @@
<form enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<button .btn .btn-primary type=submit onclick="$('#clonemodal').modal('show');">Use this drive</button> #
<a .btn href="@{AddDriveR}">
Rescan for removable drives

View file

@ -27,7 +27,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit onclick="$('#workingmodal').modal('show');">
Add Glacier repository

View file

@ -25,7 +25,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit onclick="$('#workingmodal').modal('show');">
Add S3 repository

View file

@ -16,7 +16,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit>
Save Changes

View file

@ -17,7 +17,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit onclick="$('#workingmodal').modal('show');">
Enable Amazon repository

View file

@ -9,7 +9,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit onclick="$('#workingmodal').modal('show');">
Enable repository

View file

@ -29,7 +29,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit>
$if start

View file

@ -19,7 +19,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit onclick="$('#testmodal').modal('show');">
Check this server

View file

@ -18,7 +18,7 @@
<i .icon-warning-sign></i> #{msg}
$of _
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .modal .fade #testmodal>
<div .modal-header>
<h3>

View file

@ -21,7 +21,7 @@
<form .form-horizontal enctype=#{enctype}>
<fieldset>
^{form}
^{authtoken}
^{webAppFormAuthToken}
<div .form-actions>
<button .btn .btn-primary type=submit onclick="$('#workingmodal').modal('show');">
Use this account