improve error display when storing to an export/import remote fails
Prompted by the test suite on windows failing to with "export foo failed" and no information about what went wrong. Note that only storeExportWithContentIdentifier has been converted. storeExport still returns a Bool and so exceptions may be hidden. However, storeExportWithContentIdentifier has many more failure modes, since it needs to avoid overwriting modified files. So it's more important it have better error display.
This commit is contained in:
parent
05d52f9699
commit
5004381dd9
6 changed files with 37 additions and 33 deletions
|
@ -291,17 +291,19 @@ retrieveExportWithContentIdentifierM serial adir loc cid dest mkkey _p = catchDe
|
||||||
where
|
where
|
||||||
src = androidExportLocation adir loc
|
src = androidExportLocation adir loc
|
||||||
|
|
||||||
storeExportWithContentIdentifierM :: AndroidSerial -> AndroidPath -> FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex (Maybe ContentIdentifier)
|
storeExportWithContentIdentifierM :: AndroidSerial -> AndroidPath -> FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex (Either String ContentIdentifier)
|
||||||
storeExportWithContentIdentifierM serial adir src _k loc overwritablecids _p = catchDefaultIO Nothing $
|
storeExportWithContentIdentifierM serial adir src _k loc overwritablecids _p =
|
||||||
-- Check if overwrite is safe before sending, because sending the
|
-- Check if overwrite is safe before sending, because sending the
|
||||||
-- file is expensive and don't want to do it unncessarily.
|
-- file is expensive and don't want to do it unncessarily.
|
||||||
ifM checkcanoverwrite
|
ifM checkcanoverwrite
|
||||||
( ifM (store'' serial dest src checkcanoverwrite)
|
( ifM (store'' serial dest src checkcanoverwrite)
|
||||||
( liftIO $ either (const Nothing) id
|
( liftIO $ getExportContentIdentifier serial adir loc >>= return . \case
|
||||||
<$> getExportContentIdentifier serial adir loc
|
Right (Just cid) -> Right cid
|
||||||
, return Nothing
|
Right Nothing -> Left "adb failed to store file"
|
||||||
|
Left _ -> Left "unable to get content identifier for file stored on adtb"
|
||||||
|
, return $ Left "adb failed to store file"
|
||||||
)
|
)
|
||||||
, return Nothing
|
, return $ Left "unsafe to overwrite file"
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
dest = androidExportLocation adir loc
|
dest = androidExportLocation adir loc
|
||||||
|
@ -377,6 +379,7 @@ mkAdbCommand :: AndroidSerial -> [CommandParam] -> [CommandParam]
|
||||||
mkAdbCommand serial cmd = [Param "-s", Param (fromAndroidSerial serial)] ++ cmd
|
mkAdbCommand serial cmd = [Param "-s", Param (fromAndroidSerial serial)] ++ cmd
|
||||||
|
|
||||||
-- Gets the current content identifier for a file on the android device.
|
-- Gets the current content identifier for a file on the android device.
|
||||||
|
-- If the file is not present, returns Right Nothing
|
||||||
getExportContentIdentifier :: AndroidSerial -> AndroidPath -> ExportLocation -> IO (Either ExitCode (Maybe ContentIdentifier))
|
getExportContentIdentifier :: AndroidSerial -> AndroidPath -> ExportLocation -> IO (Either ExitCode (Maybe ContentIdentifier))
|
||||||
getExportContentIdentifier serial adir loc = liftIO $ do
|
getExportContentIdentifier serial adir loc = liftIO $ do
|
||||||
ls <- adbShellRaw serial $ unwords
|
ls <- adbShellRaw serial $ unwords
|
||||||
|
|
|
@ -395,20 +395,22 @@ retrieveExportWithContentIdentifierM dir loc cid dest mkkey p =
|
||||||
| currcid == Just cid = cont
|
| currcid == Just cid = cont
|
||||||
| otherwise = return Nothing
|
| otherwise = return Nothing
|
||||||
|
|
||||||
storeExportWithContentIdentifierM :: FilePath -> FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex (Maybe ContentIdentifier)
|
storeExportWithContentIdentifierM :: FilePath -> FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex (Either String ContentIdentifier)
|
||||||
storeExportWithContentIdentifierM dir src _k loc overwritablecids p =
|
storeExportWithContentIdentifierM dir src _k loc overwritablecids p =
|
||||||
catchDefaultIO Nothing $ do
|
catchIO go (return . Left . show)
|
||||||
|
where
|
||||||
|
go = do
|
||||||
liftIO $ createDirectoryIfMissing True destdir
|
liftIO $ createDirectoryIfMissing True destdir
|
||||||
withTmpFileIn destdir template $ \tmpf tmph -> do
|
withTmpFileIn destdir template $ \tmpf tmph -> do
|
||||||
liftIO $ withMeteredFile src p (L.hPut tmph)
|
liftIO $ withMeteredFile src p (L.hPut tmph)
|
||||||
liftIO $ hFlush tmph
|
liftIO $ hFlush tmph
|
||||||
liftIO (getFileStatus tmpf) >>= liftIO . mkContentIdentifier tmpf >>= \case
|
liftIO (getFileStatus tmpf) >>= liftIO . mkContentIdentifier tmpf >>= \case
|
||||||
Nothing -> return Nothing
|
Nothing ->
|
||||||
|
return $ Left "unable to generate content identifier"
|
||||||
Just newcid ->
|
Just newcid ->
|
||||||
checkExportContent dir loc (newcid:overwritablecids) Nothing $ const $ do
|
checkExportContent dir loc (newcid:overwritablecids) (Left "unsafe to overwrite file") $ const $ do
|
||||||
liftIO $ rename tmpf dest
|
liftIO $ rename tmpf dest
|
||||||
return (Just newcid)
|
return (Right newcid)
|
||||||
where
|
|
||||||
dest = exportPath dir loc
|
dest = exportPath dir loc
|
||||||
(destdir, base) = splitFileName dest
|
(destdir, base) = splitFileName dest
|
||||||
template = relatedTemplate (base ++ ".tmp")
|
template = relatedTemplate (base ++ ".tmp")
|
||||||
|
|
|
@ -57,7 +57,7 @@ instance HasImportUnsupported (ImportActions Annex) where
|
||||||
importUnsupported = ImportActions
|
importUnsupported = ImportActions
|
||||||
{ listImportableContents = return Nothing
|
{ listImportableContents = return Nothing
|
||||||
, retrieveExportWithContentIdentifier = \_ _ _ _ _ -> return Nothing
|
, retrieveExportWithContentIdentifier = \_ _ _ _ _ -> return Nothing
|
||||||
, storeExportWithContentIdentifier = \_ _ _ _ _ -> return Nothing
|
, storeExportWithContentIdentifier = \_ _ _ _ _ -> return (Left "import not supported")
|
||||||
, removeExportWithContentIdentifier = \_ _ _ -> return False
|
, removeExportWithContentIdentifier = \_ _ _ -> return False
|
||||||
, removeExportDirectoryWhenEmpty = Just $ \_ -> return False
|
, removeExportDirectoryWhenEmpty = Just $ \_ -> return False
|
||||||
, checkPresentExportWithContentIdentifier = \_ _ _ -> return False
|
, checkPresentExportWithContentIdentifier = \_ _ _ -> return False
|
||||||
|
@ -154,8 +154,10 @@ adjustExportImport r = case M.lookup "exporttree" (config r) of
|
||||||
oldcids <- liftIO $ concat
|
oldcids <- liftIO $ concat
|
||||||
<$> mapM (ContentIdentifier.getContentIdentifiers db (uuid r')) oldks
|
<$> mapM (ContentIdentifier.getContentIdentifiers db (uuid r')) oldks
|
||||||
storeExportWithContentIdentifier (importActions r') f k loc oldcids p >>= \case
|
storeExportWithContentIdentifier (importActions r') f k loc oldcids p >>= \case
|
||||||
Nothing -> return False
|
Left err -> do
|
||||||
Just newcid -> do
|
warning err
|
||||||
|
return False
|
||||||
|
Right newcid -> do
|
||||||
withExclusiveLock gitAnnexContentIdentifierLock $ do
|
withExclusiveLock gitAnnexContentIdentifierLock $ do
|
||||||
liftIO $ ContentIdentifier.recordContentIdentifier db (uuid r') newcid k
|
liftIO $ ContentIdentifier.recordContentIdentifier db (uuid r') newcid k
|
||||||
liftIO $ ContentIdentifier.flushDbQueue db
|
liftIO $ ContentIdentifier.flushDbQueue db
|
||||||
|
|
|
@ -65,18 +65,17 @@ readonlyRemoveExportDirectory _ = readonlyFail
|
||||||
readonlyRenameExport :: Key -> ExportLocation -> ExportLocation -> Annex (Maybe Bool)
|
readonlyRenameExport :: Key -> ExportLocation -> ExportLocation -> Annex (Maybe Bool)
|
||||||
readonlyRenameExport _ _ _ = return Nothing
|
readonlyRenameExport _ _ _ = return Nothing
|
||||||
|
|
||||||
readonlyStoreExportWithContentIdentifier :: FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex (Maybe ContentIdentifier)
|
readonlyStoreExportWithContentIdentifier :: FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex (Either String ContentIdentifier)
|
||||||
readonlyStoreExportWithContentIdentifier _ _ _ _ _ = do
|
readonlyStoreExportWithContentIdentifier _ _ _ _ _ =
|
||||||
readonlyWarning
|
return $ Left readonlyWarning
|
||||||
return Nothing
|
|
||||||
|
|
||||||
readonlyRemoveExportWithContentIdentifier :: Key -> ExportLocation -> [ContentIdentifier] -> Annex Bool
|
readonlyRemoveExportWithContentIdentifier :: Key -> ExportLocation -> [ContentIdentifier] -> Annex Bool
|
||||||
readonlyRemoveExportWithContentIdentifier _ _ _ = readonlyFail
|
readonlyRemoveExportWithContentIdentifier _ _ _ = readonlyFail
|
||||||
|
|
||||||
readonlyFail :: Annex Bool
|
readonlyFail :: Annex Bool
|
||||||
readonlyFail = do
|
readonlyFail = do
|
||||||
readonlyWarning
|
warning readonlyWarning
|
||||||
return False
|
return False
|
||||||
|
|
||||||
readonlyWarning :: Annex ()
|
readonlyWarning :: String
|
||||||
readonlyWarning = warning "this remote is readonly"
|
readonlyWarning = "this remote is readonly"
|
||||||
|
|
18
Remote/S3.hs
18
Remote/S3.hs
|
@ -575,7 +575,7 @@ rewritePreconditionException a = catchJust (Url.matchStatusCodeException want) a
|
||||||
--
|
--
|
||||||
-- When the bucket is not versioned, data loss can result.
|
-- When the bucket is not versioned, data loss can result.
|
||||||
-- This is why that configuration requires --force to enable.
|
-- This is why that configuration requires --force to enable.
|
||||||
storeExportWithContentIdentifierS3 :: S3HandleVar -> Remote -> S3Info -> Maybe Magic -> FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex (Maybe ContentIdentifier)
|
storeExportWithContentIdentifierS3 :: S3HandleVar -> Remote -> S3Info -> Maybe Magic -> FilePath -> Key -> ExportLocation -> [ContentIdentifier] -> MeterUpdate -> Annex (Either String ContentIdentifier)
|
||||||
storeExportWithContentIdentifierS3 hv r info magic src k loc _overwritablecids p
|
storeExportWithContentIdentifierS3 hv r info magic src k loc _overwritablecids p
|
||||||
| versioning info = go
|
| versioning info = go
|
||||||
-- FIXME Actual aws version that supports getting Etag for a store
|
-- FIXME Actual aws version that supports getting Etag for a store
|
||||||
|
@ -584,20 +584,18 @@ storeExportWithContentIdentifierS3 hv r info magic src k loc _overwritablecids p
|
||||||
#if MIN_VERSION_aws(0,99,0)
|
#if MIN_VERSION_aws(0,99,0)
|
||||||
| otherwise = go
|
| otherwise = go
|
||||||
#else
|
#else
|
||||||
| otherwise = do
|
| otherwise = return $
|
||||||
warning "git-annex is built with too old a version of the aws library to support this operation"
|
Left "git-annex is built with too old a version of the aws library to support this operation"
|
||||||
return Nothing
|
|
||||||
#endif
|
#endif
|
||||||
where
|
where
|
||||||
go = storeExportS3' hv r info magic src k loc p >>= \case
|
go = storeExportS3' hv r info magic src k loc p >>= \case
|
||||||
(False, _) -> return Nothing
|
(False, _) -> return $ Left "failed to store content in S3 bucket"
|
||||||
(True, (_, Just vid)) -> return $ Just $
|
(True, (_, Just vid)) -> return $ Right $
|
||||||
mkS3VersionedContentIdentifier vid
|
mkS3VersionedContentIdentifier vid
|
||||||
(True, (Just etag, Nothing)) -> return $ Just $
|
(True, (Just etag, Nothing)) -> return $ Right $
|
||||||
mkS3UnversionedContentIdentifier etag
|
mkS3UnversionedContentIdentifier etag
|
||||||
(True, (Nothing, Nothing)) -> do
|
(True, (Nothing, Nothing)) ->
|
||||||
warning "did not get ETag for store to S3 bucket"
|
return $ Left "did not get ETag for store to S3 bucket"
|
||||||
return Nothing
|
|
||||||
|
|
||||||
-- Does not guarantee that the removed object has the content identifier,
|
-- Does not guarantee that the removed object has the content identifier,
|
||||||
-- but when the bucket is versioned, the removed object content can still
|
-- but when the bucket is versioned, the removed object content can still
|
||||||
|
|
|
@ -292,7 +292,7 @@ data ImportActions a = ImportActions
|
||||||
-> [ContentIdentifier]
|
-> [ContentIdentifier]
|
||||||
-- ^ old content that it's safe to overwrite
|
-- ^ old content that it's safe to overwrite
|
||||||
-> MeterUpdate
|
-> MeterUpdate
|
||||||
-> a (Maybe ContentIdentifier)
|
-> a (Either String ContentIdentifier)
|
||||||
-- This is used rather than removeExport when a special remote
|
-- This is used rather than removeExport when a special remote
|
||||||
-- supports imports.
|
-- supports imports.
|
||||||
--
|
--
|
||||||
|
|
Loading…
Reference in a new issue