Avoid running annex.http-headers-command more than once.

This commit is contained in:
Joey Hess 2018-04-04 15:00:51 -04:00
parent 98cc34c211
commit 2ec07bc29f
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
11 changed files with 31 additions and 28 deletions

View file

@ -144,6 +144,7 @@ data AnnexState = AnnexState
, keysdbhandle :: Maybe Keys.DbHandle , keysdbhandle :: Maybe Keys.DbHandle
, cachedcurrentbranch :: Maybe Git.Branch , cachedcurrentbranch :: Maybe Git.Branch
, cachedgitenv :: Maybe [(String, String)] , cachedgitenv :: Maybe [(String, String)]
, urloptions :: Maybe UrlOptions
} }
newState :: GitConfig -> Git.Repo -> IO AnnexState newState :: GitConfig -> Git.Repo -> IO AnnexState
@ -200,6 +201,7 @@ newState c r = do
, keysdbhandle = Nothing , keysdbhandle = Nothing
, cachedcurrentbranch = Nothing , cachedcurrentbranch = Nothing
, cachedgitenv = Nothing , cachedgitenv = Nothing
, urloptions = Nothing
} }
{- Makes an Annex state object for the specified git repo. {- Makes an Annex state object for the specified git repo.

View file

@ -1,7 +1,7 @@
{- Url downloading, with git-annex user agent and configured http {- Url downloading, with git-annex user agent and configured http
- headers and wget/curl options. - headers and wget/curl options.
- -
- Copyright 2013-2014 Joey Hess <id@joeyh.name> - Copyright 2013-2018 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
@ -9,7 +9,6 @@
module Annex.Url ( module Annex.Url (
module U, module U,
withUrlOptions, withUrlOptions,
getUrlOptions,
getUserAgent, getUserAgent,
) where ) where
@ -25,16 +24,20 @@ getUserAgent :: Annex (Maybe U.UserAgent)
getUserAgent = Annex.getState $ getUserAgent = Annex.getState $
Just . fromMaybe defaultUserAgent . Annex.useragent Just . fromMaybe defaultUserAgent . Annex.useragent
getUrlOptions :: Annex U.UrlOptions withUrlOptions :: (U.UrlOptions -> Annex a) -> Annex a
getUrlOptions = mkUrlOptions withUrlOptions a = Annex.getState Annex.urloptions >>= \case
<$> getUserAgent Just uo -> a uo
<*> headers Nothing -> do
<*> options uo <- mk
Annex.changeState $ \s -> s
{ Annex.urloptions = Just uo }
a uo
where where
mk = mkUrlOptions
<$> getUserAgent
<*> headers
<*> options
headers = annexHttpHeadersCommand <$> Annex.getGitConfig >>= \case headers = annexHttpHeadersCommand <$> Annex.getGitConfig >>= \case
Just cmd -> lines <$> liftIO (readProcess "sh" ["-c", cmd]) Just cmd -> lines <$> liftIO (readProcess "sh" ["-c", cmd])
Nothing -> annexHttpHeaders <$> Annex.getGitConfig Nothing -> annexHttpHeaders <$> Annex.getGitConfig
options = map Param . annexWebOptions <$> Annex.getGitConfig options = map Param . annexWebOptions <$> Annex.getGitConfig
withUrlOptions :: (U.UrlOptions -> IO a) -> Annex a
withUrlOptions a = liftIO . a =<< getUrlOptions

View file

@ -124,8 +124,7 @@ youtubeDlTo key url dest = do
-- without it. So, this first downloads part of the content and checks -- without it. So, this first downloads part of the content and checks
-- if it's a html page; only then is youtube-dl used. -- if it's a html page; only then is youtube-dl used.
htmlOnly :: URLString -> a -> Annex a -> Annex a htmlOnly :: URLString -> a -> Annex a -> Annex a
htmlOnly url fallback a = do htmlOnly url fallback a = withUrlOptions $ \uo ->
uo <- getUrlOptions
liftIO (downloadPartial url uo htmlPrefixLength) >>= \case liftIO (downloadPartial url uo htmlPrefixLength) >>= \case
Just bs | isHtmlBs bs -> a Just bs | isHtmlBs bs -> a
_ -> return fallback _ -> return fallback

View file

@ -316,8 +316,7 @@ usingDistribution :: IO Bool
usingDistribution = isJust <$> getEnv "GIT_ANNEX_STANDLONE_ENV" usingDistribution = isJust <$> getEnv "GIT_ANNEX_STANDLONE_ENV"
downloadDistributionInfo :: Assistant (Maybe GitAnnexDistribution) downloadDistributionInfo :: Assistant (Maybe GitAnnexDistribution)
downloadDistributionInfo = do downloadDistributionInfo = Url.withUrlOptions $ \uo -> do
uo <- liftAnnex Url.getUrlOptions
gpgcmd <- liftAnnex $ gpgCmd <$> Annex.getGitConfig gpgcmd <- liftAnnex $ gpgCmd <$> Annex.getGitConfig
liftIO $ withTmpDir "git-annex.tmp" $ \tmpdir -> do liftIO $ withTmpDir "git-annex.tmp" $ \tmpdir -> do
let infof = tmpdir </> "info" let infof = tmpdir </> "info"

View file

@ -189,8 +189,7 @@ escapeHeader :: String -> String
escapeHeader = escapeURIString (\c -> isUnescapedInURI c && c /= ' ') escapeHeader = escapeURIString (\c -> isUnescapedInURI c && c /= ' ')
getRepoInfo :: RemoteConfig -> Widget getRepoInfo :: RemoteConfig -> Widget
getRepoInfo c = do getRepoInfo c = Url.withUrlOptions $ \uo ->
uo <- liftAnnex Url.getUrlOptions
exists <- liftIO $ catchDefaultIO False $ Url.exists url uo exists <- liftIO $ catchDefaultIO False $ Url.exists url uo
[whamlet| [whamlet|
<a href="#{url}"> <a href="#{url}">

View file

@ -11,6 +11,7 @@ git-annex (6.20180317) UNRELEASED; urgency=medium
* When adding a new version of a file, and annex.genmetadata is enabled, * When adding a new version of a file, and annex.genmetadata is enabled,
don't copy the data metadata from the old version of the file, don't copy the data metadata from the old version of the file,
instead use the mtime of the file. instead use the mtime of the file.
* Avoid running annex.http-headers-command more than once.
-- Joey Hess <id@joeyh.name> Mon, 19 Mar 2018 23:13:59 -0400 -- Joey Hess <id@joeyh.name> Mon, 19 Mar 2018 23:13:59 -0400

View file

@ -150,13 +150,13 @@ downloadFeed url
| Url.parseURIRelaxed url == Nothing = giveup "invalid feed url" | Url.parseURIRelaxed url == Nothing = giveup "invalid feed url"
| otherwise = do | otherwise = do
showOutput showOutput
uo <- Url.getUrlOptions Url.withUrlOptions $ \ou ->
liftIO $ withTmpFile "feed" $ \f h -> do liftIO $ withTmpFile "feed" $ \f h -> do
hClose h hClose h
ifM (Url.download url f uo) ifM (Url.download url f uo)
( parseFeedString <$> readFileStrict f ( parseFeedString <$> readFileStrict f
, return Nothing , return Nothing
) )
performDownload :: ImportFeedOptions -> Cache -> ToDownload -> Annex Bool performDownload :: ImportFeedOptions -> Cache -> ToDownload -> Annex Bool
performDownload opts cache todownload = case location todownload of performDownload opts cache todownload = case location todownload of

View file

@ -207,7 +207,8 @@ downloadTorrentFile u = do
misctmp <- fromRepo gitAnnexTmpMiscDir misctmp <- fromRepo gitAnnexTmpMiscDir
withTmpFileIn misctmp "torrent" $ \f h -> do withTmpFileIn misctmp "torrent" $ \f h -> do
liftIO $ hClose h liftIO $ hClose h
ok <- Url.withUrlOptions $ Url.download u f ok <- Url.withUrlOptions $
liftIO . Url.download u f
when ok $ when ok $
liftIO $ renameFile f torrent liftIO $ renameFile f torrent
return ok return ok

View file

@ -683,7 +683,7 @@ checkKeyUrl :: Git.Repo -> CheckPresent
checkKeyUrl r k = do checkKeyUrl r k = do
showChecking r showChecking r
us <- getWebUrls k us <- getWebUrls k
anyM (\u -> withUrlOptions $ checkBoth u (keySize k)) us anyM (\u -> withUrlOptions $ liftIO . checkBoth u (keySize k)) us
getWebUrls :: Key -> Annex [URLString] getWebUrls :: Key -> Annex [URLString]
getWebUrls key = filter supported <$> getUrls key getWebUrls key = filter supported <$> getUrls key

View file

@ -248,8 +248,7 @@ tryGitConfigRead autoinit r
return $ Right r' return $ Right r'
Left l -> return $ Left l Left l -> return $ Left l
geturlconfig = do geturlconfig = Url.withUrlOptions $ \uo -> do
uo <- Url.getUrlOptions
v <- liftIO $ withTmpFile "git-annex.tmp" $ \tmpfile h -> do v <- liftIO $ withTmpFile "git-annex.tmp" $ \tmpfile h -> do
hClose h hClose h
let url = Git.repoLocation r ++ "/config" let url = Git.repoLocation r ++ "/config"

View file

@ -108,7 +108,7 @@ checkKey' key us = firsthit us (Right False) $ \u -> do
case downloader of case downloader of
YoutubeDownloader -> youtubeDlCheck u' YoutubeDownloader -> youtubeDlCheck u'
_ -> do _ -> do
Url.withUrlOptions $ catchMsgIO . Url.withUrlOptions $ liftIO . catchMsgIO .
Url.checkBoth u' (keySize key) Url.checkBoth u' (keySize key)
where where
firsthit [] miss _ = return miss firsthit [] miss _ = return miss