2013-03-03 21:07:27 +00:00
|
|
|
{- git-annex assistant general preferences
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2013 Joey Hess <id@joeyh.name>
|
2013-03-03 21:07:27 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2013-03-04 03:27:17 +00:00
|
|
|
{-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings #-}
|
2013-03-03 21:07:27 +00:00
|
|
|
|
|
|
|
module Assistant.WebApp.Configurators.Preferences (
|
2013-03-16 22:48:23 +00:00
|
|
|
getPreferencesR,
|
|
|
|
postPreferencesR
|
2013-03-03 21:07:27 +00:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Assistant.WebApp.Common
|
|
|
|
import qualified Annex
|
|
|
|
import qualified Git
|
|
|
|
import Config
|
2020-11-04 18:20:37 +00:00
|
|
|
import Config.Files.AutoStart
|
2015-04-30 18:02:56 +00:00
|
|
|
import Annex.NumCopies
|
2013-03-03 21:07:27 +00:00
|
|
|
import Utility.DataUnits
|
2013-11-22 20:21:04 +00:00
|
|
|
import Types.Distribution
|
2020-11-19 16:50:25 +00:00
|
|
|
import Assistant.Upgrade
|
2013-03-03 21:07:27 +00:00
|
|
|
|
|
|
|
import qualified Data.Text as T
|
2020-11-04 18:20:37 +00:00
|
|
|
import qualified System.FilePath.ByteString as P
|
2013-03-03 21:07:27 +00:00
|
|
|
|
|
|
|
data PrefsForm = PrefsForm
|
|
|
|
{ diskReserve :: Text
|
|
|
|
, numCopies :: Int
|
|
|
|
, autoStart :: Bool
|
2013-11-22 20:21:04 +00:00
|
|
|
, autoUpgrade :: AutoUpgrade
|
2013-03-03 21:07:27 +00:00
|
|
|
}
|
|
|
|
|
2013-06-03 20:33:05 +00:00
|
|
|
prefsAForm :: PrefsForm -> MkAForm PrefsForm
|
2015-01-28 20:11:28 +00:00
|
|
|
prefsAForm d = PrefsForm
|
2013-03-03 21:07:27 +00:00
|
|
|
<$> areq (storageField `withNote` diskreservenote)
|
2015-01-28 20:11:28 +00:00
|
|
|
(bfs "Disk reserve") (Just $ diskReserve d)
|
2013-03-03 21:07:27 +00:00
|
|
|
<*> areq (positiveIntField `withNote` numcopiesnote)
|
2015-01-28 20:11:28 +00:00
|
|
|
(bfs "Number of copies") (Just $ numCopies d)
|
2013-03-03 21:07:27 +00:00
|
|
|
<*> areq (checkBoxField `withNote` autostartnote)
|
2015-01-28 20:11:28 +00:00
|
|
|
"Auto start" (Just $ autoStart d)
|
2013-11-22 20:21:04 +00:00
|
|
|
<*> areq (selectFieldList autoUpgradeChoices)
|
2015-01-28 20:11:28 +00:00
|
|
|
(bfs autoUpgradeLabel) (Just $ autoUpgrade d)
|
2013-03-03 21:07:27 +00:00
|
|
|
where
|
|
|
|
diskreservenote = [whamlet|<br>Avoid downloading files from other repositories when there is too little free disk space.|]
|
|
|
|
numcopiesnote = [whamlet|<br>Only drop a file after verifying that other repositories contain this many copies.|]
|
|
|
|
autostartnote = [whamlet|Start the git-annex assistant at boot or on login.|]
|
|
|
|
|
2013-11-22 20:21:04 +00:00
|
|
|
autoUpgradeChoices :: [(Text, AutoUpgrade)]
|
|
|
|
autoUpgradeChoices =
|
|
|
|
[ ("ask me", AskUpgrade)
|
|
|
|
, ("enabled", AutoUpgrade)
|
|
|
|
, ("disabled", NoAutoUpgrade)
|
|
|
|
]
|
|
|
|
autoUpgradeLabel
|
2020-11-19 16:50:25 +00:00
|
|
|
| upgradeSupported = "Auto upgrade"
|
2013-11-22 20:21:04 +00:00
|
|
|
| otherwise = "Auto restart on upgrade"
|
|
|
|
|
2013-03-03 21:07:27 +00:00
|
|
|
positiveIntField = check isPositive intField
|
|
|
|
where
|
|
|
|
isPositive i
|
|
|
|
| i > 0 = Right i
|
|
|
|
| otherwise = Left notPositive
|
|
|
|
notPositive :: Text
|
|
|
|
notPositive = "This should be 1 or more!"
|
|
|
|
|
|
|
|
storageField = check validStorage textField
|
|
|
|
where
|
|
|
|
validStorage t
|
|
|
|
| T.null t = Right t
|
|
|
|
| otherwise = case readSize dataUnits $ T.unpack t of
|
|
|
|
Nothing -> Left badParse
|
|
|
|
Just _ -> Right t
|
|
|
|
badParse :: Text
|
|
|
|
badParse = "Parse error. Expected something like \"100 megabytes\" or \"2 gb\""
|
|
|
|
|
|
|
|
getPrefs :: Annex PrefsForm
|
|
|
|
getPrefs = PrefsForm
|
|
|
|
<$> (T.pack . roughSize storageUnits False . annexDiskReserve <$> Annex.getGitConfig)
|
2014-01-21 21:08:49 +00:00
|
|
|
<*> (fromNumCopies <$> getNumCopies)
|
2013-03-03 21:07:27 +00:00
|
|
|
<*> inAutoStartFile
|
2013-11-22 20:21:04 +00:00
|
|
|
<*> (annexAutoUpgrade <$> Annex.getGitConfig)
|
2013-03-03 21:07:27 +00:00
|
|
|
|
|
|
|
storePrefs :: PrefsForm -> Annex ()
|
|
|
|
storePrefs p = do
|
|
|
|
setConfig (annexConfig "diskreserve") (T.unpack $ diskReserve p)
|
2022-03-28 19:19:52 +00:00
|
|
|
setGlobalNumCopies (configuredNumCopies $ numCopies p)
|
2014-01-20 20:47:56 +00:00
|
|
|
unsetConfig (annexConfig "numcopies") -- deprecated
|
2013-11-22 20:21:04 +00:00
|
|
|
setConfig (annexConfig "autoupgrade") (fromAutoUpgrade $ autoUpgrade p)
|
2013-03-03 21:07:27 +00:00
|
|
|
unlessM ((==) <$> pure (autoStart p) <*> inAutoStartFile) $ do
|
2019-12-09 17:49:05 +00:00
|
|
|
here <- fromRawFilePath <$> fromRepo Git.repoPath
|
2013-03-03 21:07:27 +00:00
|
|
|
liftIO $ if autoStart p
|
|
|
|
then addAutoStartFile here
|
|
|
|
else removeAutoStartFile here
|
|
|
|
|
2013-06-27 05:15:28 +00:00
|
|
|
getPreferencesR :: Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
getPreferencesR = postPreferencesR
|
2013-06-27 05:15:28 +00:00
|
|
|
postPreferencesR :: Handler Html
|
2013-03-16 22:48:23 +00:00
|
|
|
postPreferencesR = page "Preferences" (Just Configuration) $ do
|
2013-06-03 17:51:54 +00:00
|
|
|
((result, form), enctype) <- liftH $ do
|
2013-03-04 20:36:38 +00:00
|
|
|
current <- liftAnnex getPrefs
|
2014-04-18 00:07:09 +00:00
|
|
|
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $ prefsAForm current
|
2013-03-03 21:07:27 +00:00
|
|
|
case result of
|
2013-06-03 17:51:54 +00:00
|
|
|
FormSuccess new -> liftH $ do
|
2013-03-04 20:36:38 +00:00
|
|
|
liftAnnex $ storePrefs new
|
2013-03-03 21:07:27 +00:00
|
|
|
redirect ConfigurationR
|
|
|
|
_ -> $(widgetFile "configurators/preferences")
|
|
|
|
|
|
|
|
inAutoStartFile :: Annex Bool
|
|
|
|
inAutoStartFile = do
|
2020-11-03 22:34:27 +00:00
|
|
|
here <- liftIO . absPath =<< fromRepo Git.repoPath
|
2020-11-04 18:20:37 +00:00
|
|
|
any (`P.equalFilePath` here) . map toRawFilePath
|
2020-11-03 22:34:27 +00:00
|
|
|
<$> liftIO readAutoStartFile
|