split cost out into its own module

Added a function to insert a new cost into a list, which could be used to
asjust costs after a drag and drop.
This commit is contained in:
Joey Hess 2013-03-13 16:16:01 -04:00
parent 672fb29b06
commit 19c0a0d5b1
18 changed files with 103 additions and 37 deletions

View file

@ -21,12 +21,13 @@ import Logs.UUID
import Logs.Remote import Logs.Remote
import Git.Remote import Git.Remote
import Config import Config
import Config.Cost
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Map as M import qualified Data.Map as M
{- Sets up and begins syncing with a new ssh or rsync remote. -} {- Sets up and begins syncing with a new ssh or rsync remote. -}
makeSshRemote :: Bool -> SshData -> Maybe Int -> Assistant Remote makeSshRemote :: Bool -> SshData -> Maybe Cost -> Assistant Remote
makeSshRemote forcersync sshdata mcost = do makeSshRemote forcersync sshdata mcost = do
r <- liftAnnex $ r <- liftAnnex $
addRemote $ maker (sshRepoName sshdata) sshurl addRemote $ maker (sshRepoName sshdata) sshurl

View file

@ -13,6 +13,7 @@ import Assistant.Pairing
import Assistant.Pairing.Network import Assistant.Pairing.Network
import Assistant.MakeRemote import Assistant.MakeRemote
import Config import Config
import Config.Cost
import Network.Socket import Network.Socket
import qualified Data.Text as T import qualified Data.Text as T

View file

@ -13,7 +13,7 @@ import Control.Concurrent.STM
import qualified Data.Map as M import qualified Data.Map as M
data ScanInfo = ScanInfo data ScanInfo = ScanInfo
{ scanPriority :: Int { scanPriority :: Float
, fullScan :: Bool , fullScan :: Bool
} }

View file

@ -13,6 +13,7 @@ import qualified Git.Config
import qualified Git.Command import qualified Git.Command
import qualified Annex import qualified Annex
import qualified Types.Remote as Remote import qualified Types.Remote as Remote
import Config.Cost
type UnqualifiedConfigKey = String type UnqualifiedConfigKey = String
data ConfigKey = ConfigKey String data ConfigKey = ConfigKey String
@ -44,43 +45,16 @@ annexConfig key = ConfigKey $ "annex." ++ key
{- Calculates cost for a remote. Either the specific default, or as configured {- Calculates cost for a remote. Either the specific default, or as configured
- by remote.<name>.annex-cost, or if remote.<name>.annex-cost-command - by remote.<name>.annex-cost, or if remote.<name>.annex-cost-command
- is set and prints a number, that is used. -} - is set and prints a number, that is used. -}
remoteCost :: RemoteGitConfig -> Int -> Annex Int remoteCost :: RemoteGitConfig -> Cost -> Annex Cost
remoteCost c def = case remoteAnnexCostCommand c of remoteCost c def = case remoteAnnexCostCommand c of
Just cmd | not (null cmd) -> liftIO $ Just cmd | not (null cmd) -> liftIO $
(fromMaybe def . readish) <$> (fromMaybe def . readish) <$>
readProcess "sh" ["-c", cmd] readProcess "sh" ["-c", cmd]
_ -> return $ fromMaybe def $ remoteAnnexCost c _ -> return $ fromMaybe def $ remoteAnnexCost c
setRemoteCost :: Remote -> Int -> Annex () setRemoteCost :: Remote -> Cost -> Annex ()
setRemoteCost r c = setConfig (remoteConfig (Remote.repo r) "cost") (show c) setRemoteCost r c = setConfig (remoteConfig (Remote.repo r) "cost") (show c)
cheapRemoteCost :: Int
cheapRemoteCost = 100
semiCheapRemoteCost :: Int
semiCheapRemoteCost = 110
semiExpensiveRemoteCost :: Int
semiExpensiveRemoteCost = 175
expensiveRemoteCost :: Int
expensiveRemoteCost = 200
veryExpensiveRemoteCost :: Int
veryExpensiveRemoteCost = 1000
{- Adjusts a remote's cost to reflect it being encrypted. -}
encryptedRemoteCostAdj :: Int
encryptedRemoteCostAdj = 50
{- Make sure the remote cost numbers work out. -}
prop_cost_sane :: Bool
prop_cost_sane = False `notElem`
[ expensiveRemoteCost > 0
, cheapRemoteCost < semiCheapRemoteCost
, semiCheapRemoteCost < semiExpensiveRemoteCost
, semiExpensiveRemoteCost < expensiveRemoteCost
, cheapRemoteCost + encryptedRemoteCostAdj > semiCheapRemoteCost
, cheapRemoteCost + encryptedRemoteCostAdj < semiExpensiveRemoteCost
, semiCheapRemoteCost + encryptedRemoteCostAdj < expensiveRemoteCost
]
getNumCopies :: Maybe Int -> Annex Int getNumCopies :: Maybe Int -> Annex Int
getNumCopies (Just v) = return v getNumCopies (Just v) = return v
getNumCopies Nothing = annexNumCopies <$> Annex.getGitConfig getNumCopies Nothing = annexNumCopies <$> Annex.getGitConfig

79
Config/Cost.hs Normal file
View file

@ -0,0 +1,79 @@
{- Remote costs.
-
- Copyright 2011-2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Config.Cost where
{- We use a float for a cost to ensure that there is a cost in
- between any two other costs. -}
type Cost = Float
{- Some predefined default costs.
- Users setting costs in config files can be aware of these,
- and pick values relative to them. So don't change. -}
cheapRemoteCost :: Cost
cheapRemoteCost = 100
nearlyCheapRemoteCost :: Cost
nearlyCheapRemoteCost = 110
semiExpensiveRemoteCost :: Cost
semiExpensiveRemoteCost = 175
expensiveRemoteCost :: Cost
expensiveRemoteCost = 200
veryExpensiveRemoteCost :: Cost
veryExpensiveRemoteCost = 1000
{- Adjusts a remote's cost to reflect it being encrypted. -}
encryptedRemoteCostAdj :: Cost
encryptedRemoteCostAdj = 50
{- Given an ordered list of costs, and the position of one of the items
- the list, inserts a new cost into the list, in between the item
- and the item after it.
-
- If both items have the same cost, one of them will have its cost
- adjusted to make room. The costs of other items in the list are left
- unchanged.
-
- To insert the new cost before any other in the list, specify a negative
- position. To insert the new cost at the end of the list, specify a
- position longer than the list.
-}
insertCostAfter :: [Cost] -> Int -> [Cost]
insertCostAfter [] _ = error "insertCostAfter: empty list"
insertCostAfter l pos
| pos < 0 = costBetween 0 (l !! 0) : l
| nextpos > maxpos = l ++ [1 + l !! maxpos]
| item == nextitem =
let (_dup:new:l') = insertCostAfter lastsegment 0
in firstsegment ++ [costBetween item new, new] ++ l'
| otherwise =
firstsegment ++ [costBetween item nextitem ] ++ lastsegment
where
nextpos = pos + 1
maxpos = length l - 1
item = l !! pos
nextitem = l !! nextpos
(firstsegment, lastsegment) = splitAt (pos + 1) l
costBetween :: Cost -> Cost -> Cost
costBetween x y
| x == y = x
| x > y = y + (x - y) / 2
| otherwise = costBetween y x
{- Make sure the remote cost numbers work out. -}
prop_cost_sane :: Bool
prop_cost_sane = False `notElem`
[ expensiveRemoteCost > 0
, cheapRemoteCost < nearlyCheapRemoteCost
, nearlyCheapRemoteCost < semiExpensiveRemoteCost
, semiExpensiveRemoteCost < expensiveRemoteCost
, cheapRemoteCost + encryptedRemoteCostAdj > nearlyCheapRemoteCost
, nearlyCheapRemoteCost + encryptedRemoteCostAdj < semiExpensiveRemoteCost
, nearlyCheapRemoteCost + encryptedRemoteCostAdj < expensiveRemoteCost
]

View file

@ -20,6 +20,7 @@ import qualified Git.Config
import qualified Git.Construct import qualified Git.Construct
import qualified Git.Ref import qualified Git.Ref
import Config import Config
import Config.Cost
import Remote.Helper.Ssh import Remote.Helper.Ssh
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable
@ -44,7 +45,7 @@ gen r u c gc = do
bupr <- liftIO $ bup2GitRemote buprepo bupr <- liftIO $ bup2GitRemote buprepo
cst <- remoteCost gc $ cst <- remoteCost gc $
if bupLocal buprepo if bupLocal buprepo
then semiCheapRemoteCost then nearlyCheapRemoteCost
else expensiveRemoteCost else expensiveRemoteCost
(u', bupr') <- getBupUUID bupr u (u', bupr') <- getBupUUID bupr u

View file

@ -16,6 +16,7 @@ import Data.Int
import Common.Annex import Common.Annex
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import Config.Cost
import Config import Config
import Utility.FileMode import Utility.FileMode
import Remote.Helper.Special import Remote.Helper.Special

View file

@ -35,6 +35,7 @@ import qualified Annex.Branch
import qualified Utility.Url as Url import qualified Utility.Url as Url
import Utility.TempFile import Utility.TempFile
import Config import Config
import Config.Cost
import Init import Init
import Types.Key import Types.Key
import qualified Fields import qualified Fields

View file

@ -16,6 +16,7 @@ import Types.Remote
import Types.Key import Types.Key
import qualified Git import qualified Git
import Config import Config
import Config.Cost
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable
import qualified Remote.Helper.AWS as AWS import qualified Remote.Helper.AWS as AWS

View file

@ -13,7 +13,7 @@ import Common.Annex
import Types.Remote import Types.Remote
import Crypto import Crypto
import qualified Annex import qualified Annex
import Config import Config.Cost
import Utility.Base64 import Utility.Base64
{- Encryption setup for a remote. The user must specify whether to use {- Encryption setup for a remote. The user must specify whether to use

View file

@ -16,6 +16,7 @@ import Types.Remote
import Types.Key import Types.Key
import qualified Git import qualified Git
import Config import Config
import Config.Cost
import Annex.Content import Annex.Content
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable

View file

@ -15,6 +15,7 @@ import Common.Annex
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import Config import Config
import Config.Cost
import Annex.Content import Annex.Content
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable

View file

@ -21,6 +21,7 @@ import Types.Remote
import Types.Key import Types.Key
import qualified Git import qualified Git
import Config import Config
import Config.Cost
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable
import qualified Remote.Helper.AWS as AWS import qualified Remote.Helper.AWS as AWS

View file

@ -13,6 +13,7 @@ import qualified Git
import qualified Git.Construct import qualified Git.Construct
import Annex.Content import Annex.Content
import Config import Config
import Config.Cost
import Logs.Web import Logs.Web
import qualified Utility.Url as Url import qualified Utility.Url as Url
import Types.Key import Types.Key

View file

@ -24,6 +24,7 @@ import Common.Annex
import Types.Remote import Types.Remote
import qualified Git import qualified Git
import Config import Config
import Config.Cost
import Remote.Helper.Special import Remote.Helper.Special
import Remote.Helper.Encryptable import Remote.Helper.Encryptable
import Remote.Helper.Chunked import Remote.Helper.Chunked

View file

@ -42,7 +42,7 @@ import qualified Logs.Presence
import qualified Remote import qualified Remote
import qualified Types.Key import qualified Types.Key
import qualified Types.Messages import qualified Types.Messages
import qualified Config import qualified Config.Cost
import qualified Crypto import qualified Crypto
import qualified Utility.Path import qualified Utility.Path
import qualified Utility.FileMode import qualified Utility.FileMode
@ -102,7 +102,7 @@ quickcheck =
, check "prop_parentDir_basics" Utility.Path.prop_parentDir_basics , check "prop_parentDir_basics" Utility.Path.prop_parentDir_basics
, check "prop_relPathDirToFile_basics" Utility.Path.prop_relPathDirToFile_basics , check "prop_relPathDirToFile_basics" Utility.Path.prop_relPathDirToFile_basics
, check "prop_relPathDirToFile_regressionTest" Utility.Path.prop_relPathDirToFile_regressionTest , check "prop_relPathDirToFile_regressionTest" Utility.Path.prop_relPathDirToFile_regressionTest
, check "prop_cost_sane" Config.prop_cost_sane , check "prop_cost_sane" Config.Cost.prop_cost_sane
, check "prop_hmacWithCipher_sane" Crypto.prop_hmacWithCipher_sane , check "prop_hmacWithCipher_sane" Crypto.prop_hmacWithCipher_sane
, check "prop_TimeStamp_sane" Logs.UUIDBased.prop_TimeStamp_sane , check "prop_TimeStamp_sane" Logs.UUIDBased.prop_TimeStamp_sane
, check "prop_addLog_sane" Logs.UUIDBased.prop_addLog_sane , check "prop_addLog_sane" Logs.UUIDBased.prop_addLog_sane

View file

@ -16,6 +16,7 @@ import Common
import qualified Git import qualified Git
import qualified Git.Config import qualified Git.Config
import Utility.DataUnits import Utility.DataUnits
import Config.Cost
{- Main git-annex settings. Each setting corresponds to a git-config key {- Main git-annex settings. Each setting corresponds to a git-config key
- such as annex.foo -} - such as annex.foo -}
@ -77,7 +78,7 @@ extractGitConfig r = GitConfig
- key such as <remote>.annex-foo, or if that is not set, a default from - key such as <remote>.annex-foo, or if that is not set, a default from
- annex.foo -} - annex.foo -}
data RemoteGitConfig = RemoteGitConfig data RemoteGitConfig = RemoteGitConfig
{ remoteAnnexCost :: Maybe Int { remoteAnnexCost :: Maybe Cost
, remoteAnnexCostCommand :: Maybe String , remoteAnnexCostCommand :: Maybe String
, remoteAnnexIgnore :: Bool , remoteAnnexIgnore :: Bool
, remoteAnnexSync :: Bool , remoteAnnexSync :: Bool

View file

@ -17,6 +17,7 @@ import Types.Key
import Types.UUID import Types.UUID
import Types.Meters import Types.Meters
import Types.GitConfig import Types.GitConfig
import Config.Cost
type RemoteConfigKey = String type RemoteConfigKey = String
type RemoteConfig = M.Map RemoteConfigKey String type RemoteConfig = M.Map RemoteConfigKey String
@ -46,7 +47,7 @@ data RemoteA a = Remote {
-- each Remote has a human visible name -- each Remote has a human visible name
name :: String, name :: String,
-- Remotes have a use cost; higher is more expensive -- Remotes have a use cost; higher is more expensive
cost :: Int, cost :: Cost,
-- Transfers a key to the remote. -- Transfers a key to the remote.
storeKey :: Key -> AssociatedFile -> MeterUpdate -> a Bool, storeKey :: Key -> AssociatedFile -> MeterUpdate -> a Bool,
-- retrieves a key's contents to a file -- retrieves a key's contents to a file