support git remotes that need http basic auth
using git credential to get the password One thing this doesn't do is wrap the password prompting inside the prompt action. So with -J, the output can be a bit garbled.
This commit is contained in:
parent
45250c3273
commit
1883f7ef8f
12 changed files with 143 additions and 44 deletions
|
@ -780,13 +780,12 @@ saveState nocommit = doSideAction $ do
|
||||||
|
|
||||||
{- Downloads content from any of a list of urls, displaying a progress
|
{- Downloads content from any of a list of urls, displaying a progress
|
||||||
- meter. -}
|
- meter. -}
|
||||||
downloadUrl :: Key -> MeterUpdate -> [Url.URLString] -> FilePath -> Annex Bool
|
downloadUrl :: Key -> MeterUpdate -> [Url.URLString] -> FilePath -> Url.UrlOptions -> Annex Bool
|
||||||
downloadUrl k p urls file =
|
downloadUrl k p urls file uo =
|
||||||
-- Poll the file to handle configurations where an external
|
-- Poll the file to handle configurations where an external
|
||||||
-- download command is used.
|
-- download command is used.
|
||||||
meteredFile file (Just p) k $
|
meteredFile file (Just p) k $
|
||||||
Url.withUrlOptions $ \uo ->
|
anyM (\u -> Url.download p u file uo) urls
|
||||||
anyM (\u -> Url.download p u file uo) urls
|
|
||||||
|
|
||||||
{- Copies a key's content, when present, to a temp file.
|
{- Copies a key's content, when present, to a temp file.
|
||||||
- This is used to speed up some rsyncs. -}
|
- This is used to speed up some rsyncs. -}
|
||||||
|
|
20
Annex/Url.hs
20
Annex/Url.hs
|
@ -1,13 +1,14 @@
|
||||||
{- Url downloading, with git-annex user agent and configured http
|
{- Url downloading, with git-annex user agent and configured http
|
||||||
- headers, security restrictions, etc.
|
- headers, security restrictions, etc.
|
||||||
-
|
-
|
||||||
- Copyright 2013-2019 Joey Hess <id@joeyh.name>
|
- Copyright 2013-2020 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Annex.Url (
|
module Annex.Url (
|
||||||
withUrlOptions,
|
withUrlOptions,
|
||||||
|
withUrlOptionsPromptingCreds,
|
||||||
getUrlOptions,
|
getUrlOptions,
|
||||||
getUserAgent,
|
getUserAgent,
|
||||||
ipAddressesUnlimited,
|
ipAddressesUnlimited,
|
||||||
|
@ -34,6 +35,7 @@ import qualified Utility.Url as U
|
||||||
import Utility.IPAddress
|
import Utility.IPAddress
|
||||||
import Utility.HttpManagerRestricted
|
import Utility.HttpManagerRestricted
|
||||||
import Utility.Metered
|
import Utility.Metered
|
||||||
|
import Git.Credential
|
||||||
import qualified BuildInfo
|
import qualified BuildInfo
|
||||||
|
|
||||||
import Network.Socket
|
import Network.Socket
|
||||||
|
@ -64,6 +66,7 @@ getUrlOptions = Annex.getState Annex.urloptions >>= \case
|
||||||
<*> pure urldownloader
|
<*> pure urldownloader
|
||||||
<*> pure manager
|
<*> pure manager
|
||||||
<*> (annexAllowedUrlSchemes <$> Annex.getGitConfig)
|
<*> (annexAllowedUrlSchemes <$> Annex.getGitConfig)
|
||||||
|
<*> pure U.noBasicAuth
|
||||||
|
|
||||||
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])
|
||||||
|
@ -124,6 +127,21 @@ ipAddressesUnlimited =
|
||||||
withUrlOptions :: (U.UrlOptions -> Annex a) -> Annex a
|
withUrlOptions :: (U.UrlOptions -> Annex a) -> Annex a
|
||||||
withUrlOptions a = a =<< getUrlOptions
|
withUrlOptions a = a =<< getUrlOptions
|
||||||
|
|
||||||
|
-- When downloading an url, if authentication is needed, uses
|
||||||
|
-- git-credential to prompt for username and password.
|
||||||
|
withUrlOptionsPromptingCreds :: (U.UrlOptions -> Annex a) -> Annex a
|
||||||
|
withUrlOptionsPromptingCreds a = do
|
||||||
|
g <- Annex.gitRepo
|
||||||
|
uo <- getUrlOptions
|
||||||
|
a $ uo
|
||||||
|
{ U.getBasicAuth = getBasicAuthFromCredential g
|
||||||
|
-- Can't download with curl and handle basic auth,
|
||||||
|
-- so avoid using curl.
|
||||||
|
, U.urlDownloader = case U.urlDownloader uo of
|
||||||
|
U.DownloadWithCurl _ -> U.DownloadWithConduit $ U.DownloadWithCurlRestricted mempty
|
||||||
|
v -> v
|
||||||
|
}
|
||||||
|
|
||||||
checkBoth :: U.URLString -> Maybe Integer -> U.UrlOptions -> Annex Bool
|
checkBoth :: U.URLString -> Maybe Integer -> U.UrlOptions -> Annex Bool
|
||||||
checkBoth url expected_size uo =
|
checkBoth url expected_size uo =
|
||||||
liftIO (U.checkBoth url expected_size uo) >>= \case
|
liftIO (U.checkBoth url expected_size uo) >>= \case
|
||||||
|
|
|
@ -17,6 +17,8 @@ git-annex (7.20191231) UNRELEASED; urgency=medium
|
||||||
programs that use GETCONFIG/SETCONFIG are recommended to implement it.
|
programs that use GETCONFIG/SETCONFIG are recommended to implement it.
|
||||||
* init: Avoid an ugly error message when http remote has no git-annex
|
* init: Avoid an ugly error message when http remote has no git-annex
|
||||||
uuid configured.
|
uuid configured.
|
||||||
|
* Support git remotes that need http basic auth to be accessed,
|
||||||
|
using git credential to get the password.
|
||||||
|
|
||||||
-- Joey Hess <id@joeyh.name> Wed, 01 Jan 2020 12:51:40 -0400
|
-- Joey Hess <id@joeyh.name> Wed, 01 Jan 2020 12:51:40 -0400
|
||||||
|
|
||||||
|
|
|
@ -261,7 +261,7 @@ downloadWeb addunlockedmatcher o url urlinfo file =
|
||||||
go =<< downloadWith' downloader urlkey webUUID url (AssociatedFile (Just (toRawFilePath file)))
|
go =<< downloadWith' downloader urlkey webUUID url (AssociatedFile (Just (toRawFilePath file)))
|
||||||
where
|
where
|
||||||
urlkey = addSizeUrlKey urlinfo $ Backend.URL.fromUrl url Nothing
|
urlkey = addSizeUrlKey urlinfo $ Backend.URL.fromUrl url Nothing
|
||||||
downloader f p = downloadUrl urlkey p [url] f
|
downloader f p = Url.withUrlOptions $ downloadUrl urlkey p [url] f
|
||||||
go Nothing = return Nothing
|
go Nothing = return Nothing
|
||||||
-- If we downloaded a html file, try to use youtube-dl to
|
-- If we downloaded a html file, try to use youtube-dl to
|
||||||
-- extract embedded media.
|
-- extract embedded media.
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{- git credential interface
|
{- git credential interface
|
||||||
-
|
-
|
||||||
- Copyright 2019 Joey Hess <id@joeyh.name>
|
- Copyright 2019-2020 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -22,6 +22,23 @@ credentialUsername = M.lookup "username" . fromCredential
|
||||||
credentialPassword :: Credential -> Maybe String
|
credentialPassword :: Credential -> Maybe String
|
||||||
credentialPassword = M.lookup "password" . fromCredential
|
credentialPassword = M.lookup "password" . fromCredential
|
||||||
|
|
||||||
|
credentialBasicAuth :: Credential -> Maybe BasicAuth
|
||||||
|
credentialBasicAuth cred = BasicAuth
|
||||||
|
<$> credentialUsername cred
|
||||||
|
<*> credentialPassword cred
|
||||||
|
|
||||||
|
getBasicAuthFromCredential :: Repo -> GetBasicAuth
|
||||||
|
getBasicAuthFromCredential r u = do
|
||||||
|
c <- getUrlCredential u r
|
||||||
|
case credentialBasicAuth c of
|
||||||
|
Just ba -> return $ Just (ba, signalsuccess c)
|
||||||
|
Nothing -> do
|
||||||
|
signalsuccess c False
|
||||||
|
return Nothing
|
||||||
|
where
|
||||||
|
signalsuccess c True = approveUrlCredential c r
|
||||||
|
signalsuccess c False = rejectUrlCredential c r
|
||||||
|
|
||||||
-- | This may prompt the user for login information, or get cached login
|
-- | This may prompt the user for login information, or get cached login
|
||||||
-- information.
|
-- information.
|
||||||
getUrlCredential :: URLString -> Repo -> IO Credential
|
getUrlCredential :: URLString -> Repo -> IO Credential
|
||||||
|
|
|
@ -747,7 +747,7 @@ checkUrlM external url =
|
||||||
retrieveUrl :: Retriever
|
retrieveUrl :: Retriever
|
||||||
retrieveUrl = fileRetriever $ \f k p -> do
|
retrieveUrl = fileRetriever $ \f k p -> do
|
||||||
us <- getWebUrls k
|
us <- getWebUrls k
|
||||||
unlessM (downloadUrl k p us f) $
|
unlessM (withUrlOptions $ downloadUrl k p us f) $
|
||||||
giveup "failed to download content"
|
giveup "failed to download content"
|
||||||
|
|
||||||
checkKeyUrl :: Git.Repo -> CheckPresent
|
checkKeyUrl :: Git.Repo -> CheckPresent
|
||||||
|
|
|
@ -276,7 +276,7 @@ tryGitConfigRead autoinit r
|
||||||
warning $ "Unable to parse git config from " ++ configloc
|
warning $ "Unable to parse git config from " ++ configloc
|
||||||
return $ Left l
|
return $ Left l
|
||||||
|
|
||||||
geturlconfig = Url.withUrlOptions $ \uo -> do
|
geturlconfig = Url.withUrlOptionsPromptingCreds $ \uo -> do
|
||||||
v <- withTmpFile "git-annex.tmp" $ \tmpfile h -> do
|
v <- withTmpFile "git-annex.tmp" $ \tmpfile h -> do
|
||||||
liftIO $ hClose h
|
liftIO $ hClose h
|
||||||
let url = Git.repoLocation r ++ "/config"
|
let url = Git.repoLocation r ++ "/config"
|
||||||
|
@ -382,7 +382,7 @@ inAnnex' repo rmt (State connpool duc _ _) key
|
||||||
checkhttp = do
|
checkhttp = do
|
||||||
showChecking repo
|
showChecking repo
|
||||||
gc <- Annex.getGitConfig
|
gc <- Annex.getGitConfig
|
||||||
ifM (Url.withUrlOptions $ \uo -> anyM (\u -> Url.checkBoth u (fromKey keySize key) uo) (keyUrls gc repo rmt key))
|
ifM (Url.withUrlOptionsPromptingCreds $ \uo -> anyM (\u -> Url.checkBoth u (fromKey keySize key) uo) (keyUrls gc repo rmt key))
|
||||||
( return True
|
( return True
|
||||||
, giveup "not found"
|
, giveup "not found"
|
||||||
)
|
)
|
||||||
|
@ -514,7 +514,8 @@ copyFromRemote'' :: Git.Repo -> Bool -> Remote -> State -> Key -> AssociatedFile
|
||||||
copyFromRemote'' repo forcersync r st@(State connpool _ _ _) key file dest meterupdate
|
copyFromRemote'' repo forcersync r st@(State connpool _ _ _) key file dest meterupdate
|
||||||
| Git.repoIsHttp repo = unVerified $ do
|
| Git.repoIsHttp repo = unVerified $ do
|
||||||
gc <- Annex.getGitConfig
|
gc <- Annex.getGitConfig
|
||||||
Annex.Content.downloadUrl key meterupdate (keyUrls gc repo r key) dest
|
Url.withUrlOptionsPromptingCreds $
|
||||||
|
Annex.Content.downloadUrl key meterupdate (keyUrls gc repo r key) dest
|
||||||
| not $ Git.repoIsUrl repo = guardUsable repo (unVerified (return False)) $ do
|
| not $ Git.repoIsUrl repo = guardUsable repo (unVerified (return False)) $ do
|
||||||
params <- Ssh.rsyncParams r Download
|
params <- Ssh.rsyncParams r Download
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
|
|
|
@ -37,6 +37,7 @@ import Crypto
|
||||||
import Backend.Hash
|
import Backend.Hash
|
||||||
import Utility.Hash
|
import Utility.Hash
|
||||||
import Utility.SshHost
|
import Utility.SshHost
|
||||||
|
import Utility.Url
|
||||||
import Logs.Remote
|
import Logs.Remote
|
||||||
import Logs.RemoteState
|
import Logs.RemoteState
|
||||||
import qualified Utility.GitLFS as LFS
|
import qualified Utility.GitLFS as LFS
|
||||||
|
@ -283,7 +284,7 @@ discoverLFSEndpoint tro h
|
||||||
if needauth (responseStatus resp)
|
if needauth (responseStatus resp)
|
||||||
then do
|
then do
|
||||||
cred <- prompt $ inRepo $ Git.getUrlCredential (show lfsrepouri)
|
cred <- prompt $ inRepo $ Git.getUrlCredential (show lfsrepouri)
|
||||||
let endpoint' = addbasicauth cred endpoint
|
let endpoint' = addbasicauth (Git.credentialBasicAuth cred) endpoint
|
||||||
let testreq' = LFS.startTransferRequest endpoint' transfernothing
|
let testreq' = LFS.startTransferRequest endpoint' transfernothing
|
||||||
flip catchNonAsync (const (returnendpoint endpoint')) $ do
|
flip catchNonAsync (const (returnendpoint endpoint')) $ do
|
||||||
resp' <- makeSmallAPIRequest testreq'
|
resp' <- makeSmallAPIRequest testreq'
|
||||||
|
@ -303,12 +304,10 @@ discoverLFSEndpoint tro h
|
||||||
|
|
||||||
needauth status = status == unauthorized401
|
needauth status = status == unauthorized401
|
||||||
|
|
||||||
addbasicauth cred endpoint =
|
addbasicauth (Just ba) endpoint =
|
||||||
case (Git.credentialUsername cred, Git.credentialPassword cred) of
|
LFS.modifyEndpointRequest endpoint $
|
||||||
(Just u, Just p) ->
|
applyBasicAuth' ba
|
||||||
LFS.modifyEndpointRequest endpoint $
|
addbasicauth Nothing endpoint = endpoint
|
||||||
applyBasicAuth (encodeBS u) (encodeBS p)
|
|
||||||
_ -> endpoint
|
|
||||||
|
|
||||||
-- The endpoint is cached for later use.
|
-- The endpoint is cached for later use.
|
||||||
getLFSEndpoint :: LFS.TransferRequestOperation -> TVar LFSHandle -> Annex (Maybe LFS.Endpoint)
|
getLFSEndpoint :: LFS.TransferRequestOperation -> TVar LFSHandle -> Annex (Maybe LFS.Endpoint)
|
||||||
|
|
|
@ -387,7 +387,7 @@ retrieve hv r rs c info = fileRetriever $ \f k p -> withS3Handle hv $ \case
|
||||||
Left failreason -> do
|
Left failreason -> do
|
||||||
warning failreason
|
warning failreason
|
||||||
giveup "cannot download content"
|
giveup "cannot download content"
|
||||||
Right us -> unlessM (downloadUrl k p us f) $
|
Right us -> unlessM (withUrlOptions $ downloadUrl k p us f) $
|
||||||
giveup "failed to download content"
|
giveup "failed to download content"
|
||||||
|
|
||||||
retrieveHelper :: S3Info -> S3Handle -> (Either S3.Object S3VersionID) -> FilePath -> MeterUpdate -> Annex ()
|
retrieveHelper :: S3Info -> S3Handle -> (Either S3.Object S3VersionID) -> FilePath -> MeterUpdate -> Annex ()
|
||||||
|
|
|
@ -90,7 +90,7 @@ downloadKey key _af dest p = unVerified $ get =<< getWebUrls key
|
||||||
YoutubeDownloader -> do
|
YoutubeDownloader -> do
|
||||||
showOutput
|
showOutput
|
||||||
youtubeDlTo key u' dest
|
youtubeDlTo key u' dest
|
||||||
_ -> downloadUrl key p [u'] dest
|
_ -> Url.withUrlOptions $ downloadUrl key p [u'] dest
|
||||||
|
|
||||||
downloadKeyCheap :: Key -> AssociatedFile -> FilePath -> Annex Bool
|
downloadKeyCheap :: Key -> AssociatedFile -> FilePath -> Annex Bool
|
||||||
downloadKeyCheap _ _ _ = return False
|
downloadKeyCheap _ _ _ = return False
|
||||||
|
|
108
Utility/Url.hs
108
Utility/Url.hs
|
@ -1,6 +1,6 @@
|
||||||
{- Url downloading.
|
{- Url downloading.
|
||||||
-
|
-
|
||||||
- Copyright 2011-2019 Joey Hess <id@joeyh.name>
|
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- License: BSD-2-clause
|
- License: BSD-2-clause
|
||||||
-}
|
-}
|
||||||
|
@ -8,6 +8,7 @@
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
||||||
module Utility.Url (
|
module Utility.Url (
|
||||||
newManager,
|
newManager,
|
||||||
|
@ -35,6 +36,10 @@ module Utility.Url (
|
||||||
parseURIRelaxed,
|
parseURIRelaxed,
|
||||||
matchStatusCodeException,
|
matchStatusCodeException,
|
||||||
matchHttpExceptionContent,
|
matchHttpExceptionContent,
|
||||||
|
BasicAuth(..),
|
||||||
|
GetBasicAuth,
|
||||||
|
noBasicAuth,
|
||||||
|
applyBasicAuth',
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
|
@ -84,6 +89,7 @@ data UrlOptions = UrlOptions
|
||||||
, applyRequest :: Request -> Request
|
, applyRequest :: Request -> Request
|
||||||
, httpManager :: Manager
|
, httpManager :: Manager
|
||||||
, allowedSchemes :: S.Set Scheme
|
, allowedSchemes :: S.Set Scheme
|
||||||
|
, getBasicAuth :: GetBasicAuth
|
||||||
}
|
}
|
||||||
|
|
||||||
data UrlDownloader
|
data UrlDownloader
|
||||||
|
@ -101,10 +107,11 @@ defUrlOptions = UrlOptions
|
||||||
<*> pure id
|
<*> pure id
|
||||||
<*> newManager tlsManagerSettings
|
<*> newManager tlsManagerSettings
|
||||||
<*> pure (S.fromList $ map mkScheme ["http", "https", "ftp"])
|
<*> pure (S.fromList $ map mkScheme ["http", "https", "ftp"])
|
||||||
|
<*> pure noBasicAuth
|
||||||
|
|
||||||
mkUrlOptions :: Maybe UserAgent -> Headers -> UrlDownloader -> Manager -> S.Set Scheme -> UrlOptions
|
mkUrlOptions :: Maybe UserAgent -> Headers -> UrlDownloader -> Manager -> S.Set Scheme -> GetBasicAuth -> UrlOptions
|
||||||
mkUrlOptions defuseragent reqheaders urldownloader manager =
|
mkUrlOptions defuseragent reqheaders urldownloader manager getbasicauth =
|
||||||
UrlOptions useragent reqheaders urldownloader applyrequest manager
|
UrlOptions useragent reqheaders urldownloader applyrequest manager getbasicauth
|
||||||
where
|
where
|
||||||
applyrequest = \r -> r { requestHeaders = requestHeaders r ++ addedheaders }
|
applyrequest = \r -> r { requestHeaders = requestHeaders r ++ addedheaders }
|
||||||
addedheaders = uaheader ++ otherheaders
|
addedheaders = uaheader ++ otherheaders
|
||||||
|
@ -197,14 +204,14 @@ getUrlInfo url uo = case parseURIRelaxed url of
|
||||||
Nothing -> return (Right dne)
|
Nothing -> return (Right dne)
|
||||||
where
|
where
|
||||||
go :: URI -> IO (Either String UrlInfo)
|
go :: URI -> IO (Either String UrlInfo)
|
||||||
go u = case (urlDownloader uo, parseUrlRequest (show u)) of
|
go u = case (urlDownloader uo, parseRequest (show u)) of
|
||||||
(DownloadWithConduit (DownloadWithCurlRestricted r), Just req) -> catchJust
|
(DownloadWithConduit (DownloadWithCurlRestricted r), Just req) -> catchJust
|
||||||
-- When http redirects to a protocol which
|
-- When http redirects to a protocol which
|
||||||
-- conduit does not support, it will throw
|
-- conduit does not support, it will throw
|
||||||
-- a StatusCodeException with found302
|
-- a StatusCodeException with found302
|
||||||
-- and a Response with the redir Location.
|
-- and a Response with the redir Location.
|
||||||
(matchStatusCodeException (== found302))
|
(matchStatusCodeException (== found302))
|
||||||
(Right <$> existsconduit req)
|
(Right <$> existsconduit req uo)
|
||||||
(followredir r)
|
(followredir r)
|
||||||
`catchNonAsync` (const $ return $ Right dne)
|
`catchNonAsync` (const $ return $ Right dne)
|
||||||
(DownloadWithConduit (DownloadWithCurlRestricted r), Nothing)
|
(DownloadWithConduit (DownloadWithCurlRestricted r), Nothing)
|
||||||
|
@ -243,18 +250,28 @@ getUrlInfo url uo = case parseURIRelaxed url of
|
||||||
extractfilename = contentDispositionFilename . B8.toString
|
extractfilename = contentDispositionFilename . B8.toString
|
||||||
<=< lookup hContentDisposition . responseHeaders
|
<=< lookup hContentDisposition . responseHeaders
|
||||||
|
|
||||||
existsconduit req = do
|
existsconduit req uo' = do
|
||||||
let req' = headRequest (applyRequest uo req)
|
let req' = headRequest (applyRequest uo req)
|
||||||
debugM "url" (show req')
|
debugM "url" (show req')
|
||||||
runResourceT $ do
|
join $ runResourceT $ do
|
||||||
resp <- http req' (httpManager uo)
|
resp <- http req' (httpManager uo)
|
||||||
-- forces processing the response while
|
-- forces processing the response while
|
||||||
-- within the runResourceT
|
-- within the runResourceT
|
||||||
liftIO $ if responseStatus resp == ok200
|
liftIO $ if responseStatus resp == ok200
|
||||||
then found
|
then do
|
||||||
(extractlen resp)
|
let !len = extractlen resp
|
||||||
(extractfilename resp)
|
let !fn = extractfilename resp
|
||||||
else return dne
|
return $ found len fn
|
||||||
|
else if responseStatus resp == unauthorized401
|
||||||
|
then return $ getBasicAuth uo' (show (getUri req)) >>= \case
|
||||||
|
Nothing -> return dne
|
||||||
|
Just (ba, signalsuccess) -> do
|
||||||
|
ui <- existsconduit
|
||||||
|
(applyBasicAuth' ba req)
|
||||||
|
(uo' { getBasicAuth = noBasicAuth })
|
||||||
|
signalsuccess (urlExists ui)
|
||||||
|
return ui
|
||||||
|
else return $ return dne
|
||||||
|
|
||||||
existscurl u curlparams = do
|
existscurl u curlparams = do
|
||||||
output <- catchDefaultIO "" $
|
output <- catchDefaultIO "" $
|
||||||
|
@ -284,6 +301,7 @@ getUrlInfo url uo = case parseURIRelaxed url of
|
||||||
sz <- getFileSize' f stat
|
sz <- getFileSize' f stat
|
||||||
found (Just sz) Nothing
|
found (Just sz) Nothing
|
||||||
Nothing -> return dne
|
Nothing -> return dne
|
||||||
|
|
||||||
followredir r (HttpExceptionRequest _ (StatusCodeException resp _)) =
|
followredir r (HttpExceptionRequest _ (StatusCodeException resp _)) =
|
||||||
case headMaybe $ map decodeBS $ getResponseHeader hLocation resp of
|
case headMaybe $ map decodeBS $ getResponseHeader hLocation resp of
|
||||||
Just url' -> case parseURIRelaxed url' of
|
Just url' -> case parseURIRelaxed url' of
|
||||||
|
@ -334,7 +352,7 @@ download' nocurlerror meterupdate url file uo =
|
||||||
where
|
where
|
||||||
go = case parseURIRelaxed url of
|
go = case parseURIRelaxed url of
|
||||||
Just u -> checkPolicy uo u $
|
Just u -> checkPolicy uo u $
|
||||||
case (urlDownloader uo, parseUrlRequest (show u)) of
|
case (urlDownloader uo, parseRequest (show u)) of
|
||||||
(DownloadWithConduit (DownloadWithCurlRestricted r), Just req) -> catchJust
|
(DownloadWithConduit (DownloadWithCurlRestricted r), Just req) -> catchJust
|
||||||
(matchStatusCodeException (== found302))
|
(matchStatusCodeException (== found302))
|
||||||
(downloadConduit meterupdate req file uo >> return (Right ()))
|
(downloadConduit meterupdate req file uo >> return (Right ()))
|
||||||
|
@ -416,12 +434,18 @@ downloadConduit :: MeterUpdate -> Request -> FilePath -> UrlOptions -> IO ()
|
||||||
downloadConduit meterupdate req file uo =
|
downloadConduit meterupdate req file uo =
|
||||||
catchMaybeIO (getFileSize file) >>= \case
|
catchMaybeIO (getFileSize file) >>= \case
|
||||||
Just sz | sz > 0 -> resumedownload sz
|
Just sz | sz > 0 -> resumedownload sz
|
||||||
_ -> runResourceT $ do
|
_ -> join $ runResourceT $ do
|
||||||
liftIO $ debugM "url" (show req')
|
liftIO $ debugM "url" (show req')
|
||||||
resp <- http req' (httpManager uo)
|
resp <- http req' (httpManager uo)
|
||||||
if responseStatus resp == ok200
|
if responseStatus resp == ok200
|
||||||
then store zeroBytesProcessed WriteMode resp
|
then do
|
||||||
else respfailure resp
|
store zeroBytesProcessed WriteMode resp
|
||||||
|
return (return ())
|
||||||
|
else if responseStatus resp == unauthorized401
|
||||||
|
then return $ getBasicAuth uo (show (getUri req')) >>= \case
|
||||||
|
Nothing -> respfailure resp
|
||||||
|
Just ba -> retryauthed ba
|
||||||
|
else return $ respfailure resp
|
||||||
where
|
where
|
||||||
req' = applyRequest uo $ req
|
req' = applyRequest uo $ req
|
||||||
-- Override http-client's default decompression of gzip
|
-- Override http-client's default decompression of gzip
|
||||||
|
@ -440,15 +464,23 @@ downloadConduit meterupdate req file uo =
|
||||||
dl
|
dl
|
||||||
(const noop)
|
(const noop)
|
||||||
where
|
where
|
||||||
dl = runResourceT $ do
|
dl = join $ runResourceT $ do
|
||||||
let req'' = req' { requestHeaders = resumeFromHeader sz : requestHeaders req }
|
let req'' = req' { requestHeaders = resumeFromHeader sz : requestHeaders req }
|
||||||
liftIO $ debugM "url" (show req'')
|
liftIO $ debugM "url" (show req'')
|
||||||
resp <- http req'' (httpManager uo)
|
resp <- http req'' (httpManager uo)
|
||||||
if responseStatus resp == partialContent206
|
if responseStatus resp == partialContent206
|
||||||
then store (toBytesProcessed sz) AppendMode resp
|
then do
|
||||||
|
store (toBytesProcessed sz) AppendMode resp
|
||||||
|
return (return ())
|
||||||
else if responseStatus resp == ok200
|
else if responseStatus resp == ok200
|
||||||
then store zeroBytesProcessed WriteMode resp
|
then do
|
||||||
else respfailure resp
|
store zeroBytesProcessed WriteMode resp
|
||||||
|
return (return ())
|
||||||
|
else if responseStatus resp == unauthorized401
|
||||||
|
then return $ getBasicAuth uo (show (getUri req'')) >>= \case
|
||||||
|
Nothing -> respfailure resp
|
||||||
|
Just ba -> retryauthed ba
|
||||||
|
else return $ respfailure resp
|
||||||
|
|
||||||
alreadydownloaded sz s h = s == requestedRangeNotSatisfiable416
|
alreadydownloaded sz s h = s == requestedRangeNotSatisfiable416
|
||||||
&& case lookup hContentRange h of
|
&& case lookup hContentRange h of
|
||||||
|
@ -469,6 +501,18 @@ downloadConduit meterupdate req file uo =
|
||||||
|
|
||||||
respfailure = giveup . B8.toString . statusMessage . responseStatus
|
respfailure = giveup . B8.toString . statusMessage . responseStatus
|
||||||
|
|
||||||
|
retryauthed (ba, signalsuccess) = do
|
||||||
|
r <- tryNonAsync $ downloadConduit
|
||||||
|
meterupdate
|
||||||
|
(applyBasicAuth' ba req)
|
||||||
|
file
|
||||||
|
(uo { getBasicAuth = noBasicAuth })
|
||||||
|
case r of
|
||||||
|
Right () -> signalsuccess True
|
||||||
|
Left e -> do
|
||||||
|
signalsuccess False
|
||||||
|
throwM e
|
||||||
|
|
||||||
{- Sinks a Response's body to a file. The file can either be opened in
|
{- Sinks a Response's body to a file. The file can either be opened in
|
||||||
- WriteMode or AppendMode. Updates the meter as data is received.
|
- WriteMode or AppendMode. Updates the meter as data is received.
|
||||||
-
|
-
|
||||||
|
@ -502,7 +546,7 @@ downloadPartial url uo n = case parseURIRelaxed url of
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
Just u -> go u `catchNonAsync` const (return Nothing)
|
Just u -> go u `catchNonAsync` const (return Nothing)
|
||||||
where
|
where
|
||||||
go u = case parseUrlRequest (show u) of
|
go u = case parseRequest (show u) of
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
Just req -> do
|
Just req -> do
|
||||||
let req' = applyRequest uo req
|
let req' = applyRequest uo req
|
||||||
|
@ -517,9 +561,6 @@ parseURIRelaxed :: URLString -> Maybe URI
|
||||||
parseURIRelaxed s = maybe (parseURIRelaxed' s) Just $
|
parseURIRelaxed s = maybe (parseURIRelaxed' s) Just $
|
||||||
parseURI $ escapeURIString isAllowedInURI s
|
parseURI $ escapeURIString isAllowedInURI s
|
||||||
|
|
||||||
parseUrlRequest :: URLString -> Maybe Request
|
|
||||||
parseUrlRequest = parseUrlThrow
|
|
||||||
|
|
||||||
{- Some characters like '[' are allowed in eg, the address of
|
{- Some characters like '[' are allowed in eg, the address of
|
||||||
- an uri, but cannot appear unescaped further along in the uri.
|
- an uri, but cannot appear unescaped further along in the uri.
|
||||||
- This handles that, expensively, by successively escaping each character
|
- This handles that, expensively, by successively escaping each character
|
||||||
|
@ -628,3 +669,22 @@ curlRestrictedParams r u defport ps = case uriAuthority u of
|
||||||
, Param "--max-redirs", Param "0"
|
, Param "--max-redirs", Param "0"
|
||||||
]
|
]
|
||||||
bracketaddr a = "[" ++ a ++ "]"
|
bracketaddr a = "[" ++ a ++ "]"
|
||||||
|
|
||||||
|
data BasicAuth = BasicAuth
|
||||||
|
{ basicAuthUser :: String
|
||||||
|
, basicAuthPassword :: String
|
||||||
|
}
|
||||||
|
|
||||||
|
-- Note that this is only used when using conduit, not curl.
|
||||||
|
--
|
||||||
|
-- The returned IO action is run after trying to use the BasicAuth,
|
||||||
|
-- indicating if the password worked.
|
||||||
|
type GetBasicAuth = URLString -> IO (Maybe (BasicAuth, Bool -> IO ()))
|
||||||
|
|
||||||
|
noBasicAuth :: GetBasicAuth
|
||||||
|
noBasicAuth = const $ pure Nothing
|
||||||
|
|
||||||
|
applyBasicAuth' :: BasicAuth -> Request -> Request
|
||||||
|
applyBasicAuth' ba = applyBasicAuth
|
||||||
|
(encodeBS (basicAuthUser ba))
|
||||||
|
(encodeBS (basicAuthPassword ba))
|
||||||
|
|
|
@ -145,3 +145,6 @@ git annex 7.20190819+git2-g908476a9b-1~ndall+1 and the same with bleeding edge 7
|
||||||
[[!meta author=yoh]]
|
[[!meta author=yoh]]
|
||||||
[[!tag projects/dandi]]
|
[[!tag projects/dandi]]
|
||||||
|
|
||||||
|
> [[done]]; the error message is improved and also git remotes that need
|
||||||
|
> http basic auth to access will get password from `git credential`.
|
||||||
|
> --[[Joey]]
|
||||||
|
|
Loading…
Reference in a new issue