adb: Better messages when the adb command is not installed

After a user completely ignored the display of the exception probably
because it didn't make sense..

This does make it a little bit slower since it checks adb is in path each
time before running it. Also, it might display a lot of warnings about it
not being installed.

This commit was sponsored by Ilya Shlyakhter on Patreon.
This commit is contained in:
Joey Hess 2020-04-02 10:46:46 -04:00
parent 23c1809aab
commit 7ebc118776
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
2 changed files with 39 additions and 25 deletions

View file

@ -2,6 +2,7 @@ git-annex (8.20200331) UNRELEASED; urgency=medium
* Improve git-annex's ability to find the path to its program, * Improve git-annex's ability to find the path to its program,
especially when it needs to run itself in another repo to upgrade it. especially when it needs to run itself in another repo to upgrade it.
* adb: Better messages when the adb command is not installed.
-- Joey Hess <id@joeyh.name> Mon, 30 Mar 2020 15:58:34 -0400 -- Joey Hess <id@joeyh.name> Mon, 30 Mar 2020 15:58:34 -0400

View file

@ -128,12 +128,12 @@ adbSetup _ mu _ c gc = do
(giveup "Specify androiddirectory=") (giveup "Specify androiddirectory=")
(pure . AndroidPath . fromProposedAccepted) (pure . AndroidPath . fromProposedAccepted)
(M.lookup androiddirectoryField c) (M.lookup androiddirectoryField c)
serial <- getserial =<< liftIO enumerateAdbConnected serial <- getserial =<< enumerateAdbConnected
let c' = M.insert androidserialField (Proposed (fromAndroidSerial serial)) c let c' = M.insert androidserialField (Proposed (fromAndroidSerial serial)) c
(c'', _encsetup) <- encryptionSetup c' gc (c'', _encsetup) <- encryptionSetup c' gc
ok <- liftIO $ adbShellBool serial ok <- adbShellBool serial
[Param "mkdir", Param "-p", File (fromAndroidPath adir)] [Param "mkdir", Param "-p", File (fromAndroidPath adir)]
unless ok $ unless ok $
giveup "Creating directory on Android device failed." giveup "Creating directory on Android device failed."
@ -166,15 +166,15 @@ store' :: AndroidSerial -> AndroidPath -> FilePath -> Annex Bool
store' serial dest src = store'' serial dest src (return True) store' serial dest src = store'' serial dest src (return True)
store'' :: AndroidSerial -> AndroidPath -> FilePath -> Annex Bool -> Annex Bool store'' :: AndroidSerial -> AndroidPath -> FilePath -> Annex Bool -> Annex Bool
store'' serial dest src canoverwrite = do store'' serial dest src canoverwrite = checkAdbInPath False $ do
let destdir = takeDirectory $ fromAndroidPath dest let destdir = takeDirectory $ fromAndroidPath dest
liftIO $ void $ adbShell serial [Param "mkdir", Param "-p", File destdir] void $ adbShell serial [Param "mkdir", Param "-p", File destdir]
showOutput -- make way for adb push output showOutput -- make way for adb push output
let tmpdest = fromAndroidPath dest ++ ".annextmp" let tmpdest = fromAndroidPath dest ++ ".annextmp"
ifM (liftIO $ boolSystem "adb" (mkAdbCommand serial [Param "push", File src, File tmpdest])) ifM (liftIO $ boolSystem "adb" (mkAdbCommand serial [Param "push", File src, File tmpdest]))
( ifM canoverwrite ( ifM canoverwrite
-- move into place atomically -- move into place atomically
( liftIO $ adbShellBool serial [Param "mv", File tmpdest, File (fromAndroidPath dest)] ( adbShellBool serial [Param "mv", File tmpdest, File (fromAndroidPath dest)]
, do , do
void $ remove' serial (AndroidPath tmpdest) void $ remove' serial (AndroidPath tmpdest)
return False return False
@ -189,7 +189,7 @@ retrieve serial adir = fileRetriever $ \dest k _p ->
giveup "adb pull failed" giveup "adb pull failed"
retrieve' :: AndroidSerial -> AndroidPath -> FilePath -> Annex Bool retrieve' :: AndroidSerial -> AndroidPath -> FilePath -> Annex Bool
retrieve' serial src dest = do retrieve' serial src dest = checkAdbInPath False $ do
showOutput -- make way for adb pull output showOutput -- make way for adb pull output
liftIO $ boolSystem "adb" $ mkAdbCommand serial liftIO $ boolSystem "adb" $ mkAdbCommand serial
[ Param "pull" [ Param "pull"
@ -201,7 +201,7 @@ remove :: AndroidSerial -> AndroidPath -> Remover
remove serial adir k = remove' serial (androidLocation adir k) remove serial adir k = remove' serial (androidLocation adir k)
remove' :: AndroidSerial -> AndroidPath -> Annex Bool remove' :: AndroidSerial -> AndroidPath -> Annex Bool
remove' serial aloc = liftIO $ adbShellBool serial remove' serial aloc = adbShellBool serial
[Param "rm", Param "-f", File (fromAndroidPath aloc)] [Param "rm", Param "-f", File (fromAndroidPath aloc)]
checkKey :: Remote -> AndroidSerial -> AndroidPath -> CheckPresent checkKey :: Remote -> AndroidSerial -> AndroidPath -> CheckPresent
@ -210,7 +210,7 @@ checkKey r serial adir k = checkKey' r serial (androidLocation adir k)
checkKey' :: Remote -> AndroidSerial -> AndroidPath -> Annex Bool checkKey' :: Remote -> AndroidSerial -> AndroidPath -> Annex Bool
checkKey' r serial aloc = do checkKey' r serial aloc = do
showChecking r showChecking r
out <- liftIO $ adbShellRaw serial $ unwords out <- adbShellRaw serial $ unwords
[ "if test -e ", shellEscape (fromAndroidPath aloc) [ "if test -e ", shellEscape (fromAndroidPath aloc)
, "; then echo y" , "; then echo y"
, "; else echo n" , "; else echo n"
@ -247,7 +247,7 @@ removeExportM serial adir _k loc = remove' serial aloc
aloc = androidExportLocation adir loc aloc = androidExportLocation adir loc
removeExportDirectoryM :: AndroidSerial -> AndroidPath -> ExportDirectory -> Annex Bool removeExportDirectoryM :: AndroidSerial -> AndroidPath -> ExportDirectory -> Annex Bool
removeExportDirectoryM serial abase dir = liftIO $ adbShellBool serial removeExportDirectoryM serial abase dir = adbShellBool serial
[Param "rm", Param "-rf", File (fromAndroidPath adir)] [Param "rm", Param "-rf", File (fromAndroidPath adir)]
where where
adir = androidExportLocation abase (mkExportLocation (fromExportDirectory dir)) adir = androidExportLocation abase (mkExportLocation (fromExportDirectory dir))
@ -258,14 +258,19 @@ checkPresentExportM r serial adir _k loc = checkKey' r serial aloc
aloc = androidExportLocation adir loc aloc = androidExportLocation adir loc
renameExportM :: AndroidSerial -> AndroidPath -> Key -> ExportLocation -> ExportLocation -> Annex (Maybe Bool) renameExportM :: AndroidSerial -> AndroidPath -> Key -> ExportLocation -> ExportLocation -> Annex (Maybe Bool)
renameExportM serial adir _k old new = liftIO $ Just <$> renameExportM serial adir _k old new = Just <$> adbShellBool serial ps
adbShellBool serial [Param "mv", Param "-f", File oldloc, File newloc]
where where
oldloc = fromAndroidPath $ androidExportLocation adir old oldloc = fromAndroidPath $ androidExportLocation adir old
newloc = fromAndroidPath $ androidExportLocation adir new newloc = fromAndroidPath $ androidExportLocation adir new
ps =
[ Param "mv"
, Param "-f"
, File oldloc
, File newloc
]
listImportableContentsM :: AndroidSerial -> AndroidPath -> Annex (Maybe (ImportableContents (ContentIdentifier, ByteSize))) listImportableContentsM :: AndroidSerial -> AndroidPath -> Annex (Maybe (ImportableContents (ContentIdentifier, ByteSize)))
listImportableContentsM serial adir = liftIO $ listImportableContentsM serial adir =
process <$> adbShell serial process <$> adbShell serial
[ Param "find" [ Param "find"
-- trailing slash is needed, or android's find command -- trailing slash is needed, or android's find command
@ -300,7 +305,7 @@ retrieveExportWithContentIdentifierM serial adir loc cid dest mkkey _p = catchDe
ifM (retrieve' serial src dest) ifM (retrieve' serial src dest)
( do ( do
k <- mkkey k <- mkkey
currcid <- liftIO $ getExportContentIdentifier serial adir loc currcid <- getExportContentIdentifier serial adir loc
return $ if currcid == Right (Just cid) return $ if currcid == Right (Just cid)
then k then k
else Nothing else Nothing
@ -315,7 +320,7 @@ storeExportWithContentIdentifierM serial adir src _k loc overwritablecids _p =
-- 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 $ getExportContentIdentifier serial adir loc >>= return . \case ( getExportContentIdentifier serial adir loc >>= return . \case
Right (Just cid) -> Right cid Right (Just cid) -> Right cid
Right Nothing -> Left "adb failed to store file" Right Nothing -> Left "adb failed to store file"
Left _ -> Left "unable to get content identifier for file stored on adtb" Left _ -> Left "unable to get content identifier for file stored on adtb"
@ -325,7 +330,7 @@ storeExportWithContentIdentifierM serial adir src _k loc overwritablecids _p =
) )
where where
dest = androidExportLocation adir loc dest = androidExportLocation adir loc
checkcanoverwrite = liftIO $ checkcanoverwrite =
getExportContentIdentifier serial adir loc >>= return . \case getExportContentIdentifier serial adir loc >>= return . \case
Right (Just cid) | cid `elem` overwritablecids -> True Right (Just cid) | cid `elem` overwritablecids -> True
Right Nothing -> True Right Nothing -> True
@ -333,7 +338,7 @@ storeExportWithContentIdentifierM serial adir src _k loc overwritablecids _p =
removeExportWithContentIdentifierM :: AndroidSerial -> AndroidPath -> Key -> ExportLocation -> [ContentIdentifier] -> Annex Bool removeExportWithContentIdentifierM :: AndroidSerial -> AndroidPath -> Key -> ExportLocation -> [ContentIdentifier] -> Annex Bool
removeExportWithContentIdentifierM serial adir k loc removeablecids = catchBoolIO $ removeExportWithContentIdentifierM serial adir k loc removeablecids = catchBoolIO $
liftIO (getExportContentIdentifier serial adir loc) >>= \case getExportContentIdentifier serial adir loc >>= \case
Right Nothing -> return True Right Nothing -> return True
Right (Just cid) | cid `elem` removeablecids -> Right (Just cid) | cid `elem` removeablecids ->
removeExportM serial adir k loc removeExportM serial adir k loc
@ -341,7 +346,7 @@ removeExportWithContentIdentifierM serial adir k loc removeablecids = catchBoolI
checkPresentExportWithContentIdentifierM :: AndroidSerial -> AndroidPath -> Key -> ExportLocation -> [ContentIdentifier] -> Annex Bool checkPresentExportWithContentIdentifierM :: AndroidSerial -> AndroidPath -> Key -> ExportLocation -> [ContentIdentifier] -> Annex Bool
checkPresentExportWithContentIdentifierM serial adir _k loc knowncids = checkPresentExportWithContentIdentifierM serial adir _k loc knowncids =
liftIO $ getExportContentIdentifier serial adir loc >>= \case getExportContentIdentifier serial adir loc >>= \case
Right (Just cid) | cid `elem` knowncids -> return True Right (Just cid) | cid `elem` knowncids -> return True
Right _ -> return False Right _ -> return False
Left _ -> giveup "unable to access Android device" Left _ -> giveup "unable to access Android device"
@ -351,8 +356,8 @@ androidExportLocation adir loc = AndroidPath $
fromAndroidPath adir ++ "/" ++ fromRawFilePath (fromExportLocation loc) fromAndroidPath adir ++ "/" ++ fromRawFilePath (fromExportLocation loc)
-- | List all connected Android devices. -- | List all connected Android devices.
enumerateAdbConnected :: IO [AndroidSerial] enumerateAdbConnected :: Annex [AndroidSerial]
enumerateAdbConnected = enumerateAdbConnected = checkAdbInPath [] $ liftIO $
mapMaybe parse . lines <$> readProcess "adb" ["devices"] mapMaybe parse . lines <$> readProcess "adb" ["devices"]
where where
parse l = parse l =
@ -364,11 +369,11 @@ enumerateAdbConnected =
-- | Runs a command on the android device with the given serial number. -- | Runs a command on the android device with the given serial number.
-- --
-- Any stdout from the command is returned, separated into lines. -- Any stdout from the command is returned, separated into lines.
adbShell :: AndroidSerial -> [CommandParam] -> IO (Maybe [String]) adbShell :: AndroidSerial -> [CommandParam] -> Annex (Maybe [String])
adbShell serial cmd = adbShellRaw serial $ adbShell serial cmd = adbShellRaw serial $
unwords $ map shellEscape (toCommand cmd) unwords $ map shellEscape (toCommand cmd)
adbShellBool :: AndroidSerial -> [CommandParam] -> IO Bool adbShellBool :: AndroidSerial -> [CommandParam] -> Annex Bool
adbShellBool serial cmd = adbShellBool serial cmd =
adbShellRaw serial cmd' >>= return . \case adbShellRaw serial cmd' >>= return . \case
Just l -> end l == ["y"] Just l -> end l == ["y"]
@ -379,8 +384,8 @@ adbShellBool serial cmd =
-- | Runs a raw shell command on the android device. -- | Runs a raw shell command on the android device.
-- Any necessary shellEscaping must be done by caller. -- Any necessary shellEscaping must be done by caller.
adbShellRaw :: AndroidSerial -> String -> IO (Maybe [String]) adbShellRaw :: AndroidSerial -> String -> Annex (Maybe [String])
adbShellRaw serial cmd = catchMaybeIO $ adbShellRaw serial cmd = checkAdbInPath Nothing $ liftIO $ catchMaybeIO $
processoutput <$> readProcess "adb" processoutput <$> readProcess "adb"
[ "-s" [ "-s"
, fromAndroidSerial serial , fromAndroidSerial serial
@ -393,13 +398,21 @@ adbShellRaw serial cmd = catchMaybeIO $
-- despite both linux and android being unix systems. -- despite both linux and android being unix systems.
trimcr = takeWhile (/= '\r') trimcr = takeWhile (/= '\r')
checkAdbInPath :: a -> Annex a -> Annex a
checkAdbInPath d a = ifM (isJust <$> liftIO (searchPath "adb"))
( a
, do
warning "adb command not found in PATH. Install it to use this remote."
return d
)
mkAdbCommand :: AndroidSerial -> [CommandParam] -> [CommandParam] 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 -- If the file is not present, returns Right Nothing
getExportContentIdentifier :: AndroidSerial -> AndroidPath -> ExportLocation -> IO (Either ExitCode (Maybe ContentIdentifier)) getExportContentIdentifier :: AndroidSerial -> AndroidPath -> ExportLocation -> Annex (Either ExitCode (Maybe ContentIdentifier))
getExportContentIdentifier serial adir loc = liftIO $ do getExportContentIdentifier serial adir loc = do
ls <- adbShellRaw serial $ unwords ls <- adbShellRaw serial $ unwords
[ "if test -e ", shellEscape aloc [ "if test -e ", shellEscape aloc
, "; then stat -c" , "; then stat -c"