scan cheapest remotes first
This way, we get transfers from cheapest remotes.
This commit is contained in:
parent
546ba8b7e1
commit
ab8cb05989
1 changed files with 10 additions and 10 deletions
|
@ -8,13 +8,15 @@
|
||||||
module Assistant.ScanRemotes where
|
module Assistant.ScanRemotes where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
import Data.Function
|
import qualified Types.Remote as Remote
|
||||||
|
|
||||||
|
import Data.Function
|
||||||
import Control.Concurrent.STM
|
import Control.Concurrent.STM
|
||||||
import Data.Time.Clock
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
type ScanRemoteMap = TMVar (M.Map Remote UTCTime)
|
type Priority = Int
|
||||||
|
|
||||||
|
type ScanRemoteMap = TMVar (M.Map Remote Priority)
|
||||||
|
|
||||||
{- The TMVar starts empty, and is left empty when there are no remotes
|
{- The TMVar starts empty, and is left empty when there are no remotes
|
||||||
- to scan. -}
|
- to scan. -}
|
||||||
|
@ -22,7 +24,7 @@ newScanRemoteMap :: IO ScanRemoteMap
|
||||||
newScanRemoteMap = atomically newEmptyTMVar
|
newScanRemoteMap = atomically newEmptyTMVar
|
||||||
|
|
||||||
{- Blocks until there is a remote that needs to be scanned.
|
{- Blocks until there is a remote that needs to be scanned.
|
||||||
- Processes remotes added most recently first. -}
|
- Processes higher priority remotes first. -}
|
||||||
getScanRemote :: ScanRemoteMap -> IO Remote
|
getScanRemote :: ScanRemoteMap -> IO Remote
|
||||||
getScanRemote v = atomically $ do
|
getScanRemote v = atomically $ do
|
||||||
m <- takeTMVar v
|
m <- takeTMVar v
|
||||||
|
@ -37,9 +39,7 @@ getScanRemote v = atomically $ do
|
||||||
|
|
||||||
{- Adds new remotes that need scanning to the map. -}
|
{- Adds new remotes that need scanning to the map. -}
|
||||||
addScanRemotes :: ScanRemoteMap -> [Remote] -> IO ()
|
addScanRemotes :: ScanRemoteMap -> [Remote] -> IO ()
|
||||||
addScanRemotes _ [] = return ()
|
addScanRemotes _ [] = noop
|
||||||
addScanRemotes v rs = do
|
addScanRemotes v rs = atomically $ do
|
||||||
now <- getCurrentTime
|
m <- fromMaybe M.empty <$> tryTakeTMVar v
|
||||||
atomically $ do
|
putTMVar v $ M.union m $ M.fromList $ map (\r -> (r, Remote.cost r)) rs
|
||||||
m <- fromMaybe M.empty <$> tryTakeTMVar v
|
|
||||||
putTMVar v $ foldr (`M.insert` now) m rs
|
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue