implemented checkPresent for git-lfs

This commit is contained in:
Joey Hess 2019-08-03 12:21:28 -04:00
parent f536a0b264
commit 5be0a35dae
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
2 changed files with 68 additions and 17 deletions

View file

@ -34,6 +34,7 @@ import Crypto
import Control.Concurrent.STM import Control.Concurrent.STM
import Data.String import Data.String
import Network.HTTP.Client import Network.HTTP.Client
import Network.HTTP.Types
import System.Log.Logger import System.Log.Logger
import qualified Data.Map as M import qualified Data.Map as M
import qualified Network.URI as URI import qualified Network.URI as URI
@ -205,7 +206,7 @@ getLFSEndpoint tro hv = do
LFS.RequestDownload -> downloadEndpoint LFS.RequestDownload -> downloadEndpoint
LFS.RequestUpload -> uploadEndpoint LFS.RequestUpload -> uploadEndpoint
-- makeAPIRequest :: Request -> Annex (Response t) makeAPIRequest :: Request -> Annex (Response L.ByteString)
makeAPIRequest req = do makeAPIRequest req = do
uo <- getUrlOptions uo <- getUrlOptions
let req' = applyRequest uo req let req' = applyRequest uo req
@ -226,11 +227,11 @@ sendTransferRequest req endpoint =
Just httpreq -> do Just httpreq -> do
httpresp <- makeAPIRequest $ setRequestCheckStatus httpreq httpresp <- makeAPIRequest $ setRequestCheckStatus httpreq
return $ case LFS.parseTransferResponse (responseBody httpresp) of return $ case LFS.parseTransferResponse (responseBody httpresp) of
Left (Right tro) -> Left $ LFS.ParsedTransferResponse resp -> Right resp
LFS.ParsedTransferResponseError tro -> Left $
T.unpack $ LFS.resperr_message tro T.unpack $ LFS.resperr_message tro
Left (Left err) -> Left err LFS.ParseFailed err -> Left err
Right resp -> Right resp Nothing -> return $ Left "unable to parse git-lfs endpoint url"
Nothing -> return (Left "unable to parse git-lfs endpoint url")
extractKeySha256 :: Key -> Maybe LFS.SHA256 extractKeySha256 :: Key -> Maybe LFS.SHA256
extractKeySha256 k = case keyVariety k of extractKeySha256 k = case keyVariety k of
@ -246,10 +247,28 @@ extractKeySize k
| isEncKey k = Nothing | isEncKey k = Nothing
| otherwise = keySize k | otherwise = keySize k
mkDownloadRequest :: Key -> Annex (Maybe LFS.TransferRequest)
mkDownloadRequest k = case (extractKeySha256 k, extractKeySize k) of
(Just sha256, Just sz) -> go sha256 sz
-- TODO get from git-annex branch
_ -> return Nothing
where
go sha256 sz = do
let obj = LFS.TransferRequestObject
{ LFS.req_oid = sha256
, LFS.req_size = sz
}
return $ Just $ LFS.TransferRequest
{ LFS.req_operation = LFS.RequestDownload
, LFS.req_transfers = [LFS.Basic]
, LFS.req_ref = Nothing
, LFS.req_objects = [obj]
}
store :: TVar LFSHandle -> Storer store :: TVar LFSHandle -> Storer
store h = fileStorer $ \k src p -> getLFSEndpoint LFS.RequestUpload h >>= \case store h = fileStorer $ \k src p -> getLFSEndpoint LFS.RequestUpload h >>= \case
Nothing -> return False Nothing -> return False
Just endpoint -> flip catchNonAsync (const $ return False) $ do Just endpoint -> flip catchNonAsync failederr $ do
sha256 <- case extractKeySha256 k of sha256 <- case extractKeySha256 k of
Just sha -> pure sha Just sha -> pure sha
Nothing -> do Nothing -> do
@ -299,6 +318,9 @@ store h = fileStorer $ \k src p -> getLFSEndpoint LFS.RequestUpload h >>= \case
Just [] -> noop -- server already has it Just [] -> noop -- server already has it
Just reqs -> forM_ reqs $ Just reqs -> forM_ reqs $
makeAPIRequest . setRequestCheckStatus makeAPIRequest . setRequestCheckStatus
failederr e = do
warning (show e)
return False
retrieve :: TVar LFSHandle -> Retriever retrieve :: TVar LFSHandle -> Retriever
retrieve h = byteRetriever $ \k sink -> getLFSEndpoint LFS.RequestDownload h >>= \case retrieve h = byteRetriever $ \k sink -> getLFSEndpoint LFS.RequestDownload h >>= \case
@ -310,9 +332,34 @@ retrieve h = byteRetriever $ \k sink -> getLFSEndpoint LFS.RequestDownload h >>=
checkKey :: TVar LFSHandle -> CheckPresent checkKey :: TVar LFSHandle -> CheckPresent
checkKey h key = getLFSEndpoint LFS.RequestDownload h >>= \case checkKey h key = getLFSEndpoint LFS.RequestDownload h >>= \case
Nothing -> giveup "unable to connect to git-lfs endpoint" Nothing -> giveup "unable to connect to git-lfs endpoint"
Just endpoint -> do Just endpoint -> mkDownloadRequest key >>= \case
liftIO $ print ("endpoint", endpoint) -- Unable to find enough information to request the key
return False -- from git-lfs, so it's not present there.
Nothing -> return False
Just req -> case LFS.startTransferRequest endpoint req of
Nothing -> giveup "unable to parse git-lfs endpoint url"
Just httpreq -> go =<< makeAPIRequest httpreq
where
go httpresp
| responseStatus httpresp == status200 =
go' $ LFS.parseTransferResponse (responseBody httpresp)
| otherwise =
giveup $ "git-lfs server refused request: " ++ show (responseStatus httpresp)
go' :: LFS.ParsedTransferResponse LFS.DownloadOperation -> Annex Bool
go' (LFS.ParseFailed err) =
giveup $ "unable to parse response from git-lfs server: " ++ err
-- If the server responds with a json error message,
-- the content is presumably not present.
go' (LFS.ParsedTransferResponseError _) = return False
-- If the server responds with at least one download operation,
-- we will assume the content is present. We could also try to HEAD
-- that download, but there's no guarantee HEAD is supported, and
-- at most that would detect breakage where the server is confused
-- about what objects it has.
go' (LFS.ParsedTransferResponse resp) =
return $ not $ null $
mapMaybe LFS.resp_actions $ LFS.objects resp
retrieveCheap :: Key -> AssociatedFile -> FilePath -> Annex Bool retrieveCheap :: Key -> AssociatedFile -> FilePath -> Annex Bool
retrieveCheap _ _ _ = return False retrieveCheap _ _ _ = return False

View file

@ -24,7 +24,7 @@ module Utility.GitLFS (
IsTransferResponseOperation, IsTransferResponseOperation,
DownloadOperation, DownloadOperation,
UploadOperation, UploadOperation,
ParsedTransferResponse, ParsedTransferResponse(..),
parseTransferResponse, parseTransferResponse,
-- * making transfers -- * making transfers
downloadOperationRequest, downloadOperationRequest,
@ -311,7 +311,9 @@ guessEndpoint uri = case URI.uriScheme uri of
_ -> Nothing _ -> Nothing
where where
endpoint = EndpointURI $ uri endpoint = EndpointURI $ uri
{ URI.uriScheme = "https" -- force https because the git-lfs protocol uses http
-- basic auth tokens, which should not be exposed
{ URI.uriScheme = "https:"
, URI.uriPath = guessedpath , URI.uriPath = guessedpath
} }
@ -357,8 +359,10 @@ addLfsJsonHeaders r = r
where where
lfsjson = "application/vnd.git-lfs+json" lfsjson = "application/vnd.git-lfs+json"
type ParsedTransferResponse op = data ParsedTransferResponse op
Either (Either String TransferResponseError) (TransferResponse op) = ParsedTransferResponse (TransferResponse op)
| ParsedTransferResponseError TransferResponseError
| ParseFailed String
-- | Parse the body of a response to a transfer request. -- | Parse the body of a response to a transfer request.
parseTransferResponse parseTransferResponse
@ -366,13 +370,13 @@ parseTransferResponse
=> L.ByteString => L.ByteString
-> ParsedTransferResponse op -> ParsedTransferResponse op
parseTransferResponse resp = case eitherDecode resp of parseTransferResponse resp = case eitherDecode resp of
Right tr -> ParsedTransferResponse tr
-- If unable to decode as a TransferResponse, try to decode -- If unable to decode as a TransferResponse, try to decode
-- as a TransferResponseError instead, in case the LFS server -- as a TransferResponseError instead, in case the LFS server
-- sent an error message. -- sent an error message.
Left err -> case eitherDecode resp of Left err ->
Right responseerror -> Left (Right responseerror) either (const $ ParseFailed err) ParsedTransferResponseError $
Left _ -> Left $ Left err eitherDecode resp
Right tr -> Right tr
-- | Builds a http request to perform a download. -- | Builds a http request to perform a download.
downloadOperationRequest :: DownloadOperation -> Maybe Request downloadOperationRequest :: DownloadOperation -> Maybe Request