simplify annex.bwlimit handling
RemoteGitConfig parsing looks for annex.bwlimit when a remote does not have a per-remote config for it, so no need for a separate gobal config. Sponsored-by: Svenne Krap on Patreon
This commit is contained in:
parent
05a097cde8
commit
798b33ba3d
6 changed files with 7 additions and 20 deletions
|
@ -461,7 +461,7 @@ importKeys remote importtreeconfig importcontent thirdpartypopulated importablec
|
|||
, providedMimeEncoding = Nothing
|
||||
, providedLinkType = Nothing
|
||||
}
|
||||
bwlimit <- bwLimit (Remote.gitconfig remote)
|
||||
let bwlimit = remoteAnnexBwLimit (Remote.gitconfig remote)
|
||||
islargefile <- checkMatcher' matcher mi mempty
|
||||
metered Nothing sz bwlimit $ const $ if islargefile
|
||||
then doimportlarge importkey cidmap db loc cid sz f
|
||||
|
@ -558,7 +558,7 @@ importKeys remote importtreeconfig importcontent thirdpartypopulated importablec
|
|||
Left e -> do
|
||||
warning (show e)
|
||||
return Nothing
|
||||
bwlimit <- bwLimit (Remote.gitconfig remote)
|
||||
let bwlimit = remoteAnnexBwLimit (Remote.gitconfig remote)
|
||||
checkDiskSpaceToGet tmpkey Nothing $
|
||||
notifyTransfer Download af $
|
||||
download' (Remote.uuid remote) tmpkey af Nothing stdRetry $ \p ->
|
||||
|
|
|
@ -19,7 +19,6 @@ module Annex.Transfer (
|
|||
noRetry,
|
||||
stdRetry,
|
||||
pickRemote,
|
||||
bwLimit,
|
||||
) where
|
||||
|
||||
import Annex.Common
|
||||
|
@ -402,9 +401,3 @@ lessActiveFirst :: M.Map Remote Integer -> Remote -> Remote -> Ordering
|
|||
lessActiveFirst active a b
|
||||
| Remote.cost a == Remote.cost b = comparing (`M.lookup` active) a b
|
||||
| otherwise = comparing Remote.cost a b
|
||||
|
||||
bwLimit :: RemoteGitConfig -> Annex (Maybe BwRate)
|
||||
bwLimit gc = maybe globalcfg (pure . Just) remotecfg
|
||||
where
|
||||
globalcfg = annexBwLimit <$> Annex.getGitConfig
|
||||
remotecfg = remoteAnnexBwLimit gc
|
||||
|
|
|
@ -550,7 +550,7 @@ copyFromRemote'' repo forcersync r st@(State connpool _ _ _ _) key file dest met
|
|||
| not $ Git.repoIsUrl repo = guardUsable repo (giveup "cannot access remote") $ do
|
||||
u <- getUUID
|
||||
hardlink <- wantHardLink
|
||||
bwlimit <- bwLimit (gitconfig r)
|
||||
let bwlimit = remoteAnnexBwLimit (gitconfig r)
|
||||
-- run copy from perspective of remote
|
||||
onLocalFast st $ Annex.Content.prepSendAnnex' key >>= \case
|
||||
Just (object, check) -> do
|
||||
|
@ -696,7 +696,7 @@ copyToRemote' repo r st@(State connpool duc _ _ _) key file meterupdate
|
|||
checkio <- Annex.withCurrentState check
|
||||
u <- getUUID
|
||||
hardlink <- wantHardLink
|
||||
bwlimit <- bwLimit (gitconfig r)
|
||||
let bwlimit = remoteAnnexBwLimit (gitconfig r)
|
||||
-- run copy from perspective of remote
|
||||
res <- onLocalFast st $ ifM (Annex.Content.inAnnex key)
|
||||
( return True
|
||||
|
|
|
@ -18,7 +18,6 @@ import Messages.Progress
|
|||
import Utility.Metered
|
||||
import Types.NumCopies
|
||||
import Annex.Verify
|
||||
import Annex.Transfer
|
||||
|
||||
import Control.Concurrent
|
||||
|
||||
|
@ -35,7 +34,7 @@ type WithConn a c = (ClosableConnection c -> Annex (ClosableConnection c, a)) ->
|
|||
store :: RemoteGitConfig -> (MeterUpdate -> ProtoRunner Bool) -> Key -> AssociatedFile -> MeterUpdate -> Annex ()
|
||||
store gc runner k af p = do
|
||||
let sizer = KeySizer k (fmap (toRawFilePath . fst) <$> prepSendAnnex k)
|
||||
bwlimit <- bwLimit gc
|
||||
let bwlimit = remoteAnnexBwLimit gc
|
||||
metered (Just p) sizer bwlimit $ \_ p' ->
|
||||
runner p' (P2P.put k af p') >>= \case
|
||||
Just True -> return ()
|
||||
|
@ -45,7 +44,7 @@ store gc runner k af p = do
|
|||
retrieve :: RemoteGitConfig -> (MeterUpdate -> ProtoRunner (Bool, Verification)) -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> VerifyConfig -> Annex Verification
|
||||
retrieve gc runner k af dest p verifyconfig = do
|
||||
iv <- startVerifyKeyContentIncrementally verifyconfig k
|
||||
bwlimit <- bwLimit gc
|
||||
let bwlimit = remoteAnnexBwLimit gc
|
||||
metered (Just p) k bwlimit $ \m p' ->
|
||||
runner p' (P2P.get dest k iv af m p') >>= \case
|
||||
Just (True, v) -> return v
|
||||
|
|
|
@ -42,7 +42,6 @@ import Types.StoreRetrieve
|
|||
import Types.Remote
|
||||
import Annex.Verify
|
||||
import Annex.UUID
|
||||
import Annex.Transfer
|
||||
import Config
|
||||
import Config.Cost
|
||||
import Utility.Metered
|
||||
|
@ -263,7 +262,7 @@ specialRemote' cfg c storer retriever remover checkpresent baser = encr
|
|||
|
||||
displayprogress p k srcfile a
|
||||
| displayProgress cfg = do
|
||||
bwlimit <- bwLimit (gitconfig baser)
|
||||
let bwlimit = remoteAnnexBwLimit (gitconfig baser)
|
||||
metered (Just p) (KeySizer k (pure (fmap toRawFilePath srcfile))) bwlimit (const a)
|
||||
| otherwise = a p
|
||||
|
||||
|
|
|
@ -123,7 +123,6 @@ data GitConfig = GitConfig
|
|||
, annexRetry :: Maybe Integer
|
||||
, annexForwardRetry :: Maybe Integer
|
||||
, annexRetryDelay :: Maybe Seconds
|
||||
, annexBwLimit :: Maybe BwRate
|
||||
, annexAllowedUrlSchemes :: S.Set Scheme
|
||||
, annexAllowedIPAddresses :: String
|
||||
, annexAllowUnverifiedDownloads :: Bool
|
||||
|
@ -217,9 +216,6 @@ extractGitConfig configsource r = GitConfig
|
|||
, annexForwardRetry = getmayberead (annexConfig "forward-retry")
|
||||
, annexRetryDelay = Seconds
|
||||
<$> getmayberead (annexConfig "retrydelay")
|
||||
, annexBwLimit =
|
||||
either (const Nothing) Just . parseBwRate
|
||||
=<< getmaybe (annexConfig "bwlimit")
|
||||
, annexAllowedUrlSchemes = S.fromList $ map mkScheme $
|
||||
maybe ["http", "https", "ftp"] words $
|
||||
getmaybe (annexConfig "security.allowed-url-schemes")
|
||||
|
|
Loading…
Reference in a new issue