{-# LANGUAGE OverloadedStrings #-} {- | Utility functions to launch and connect to the view server -} module Adb( startViewServer , stopViewServer , isViewServerRunning , whenViewServer , adbForward ) where import System.Process import Control.Concurrent.MVar import qualified Control.Exception as C import System.IO import System.Exit ( ExitCode(..) ) import Control.Concurrent hiding(yield) import Control.Monad(when) import Control.Monad.Writer import Types -- | Run a command using arguments and a standard input -- Return a result or an error maybeProcess :: FilePath -- ^ command to run -> [String] -- ^ any arguments -> String -- ^ standard input -> IO (Either String String) -- ^ stdout maybeProcess cmd args input = do (Just inh, Just outh, _, pid) <- createProcess (proc cmd args){ std_in = CreatePipe, std_out = CreatePipe, std_err = CreatePipe } -- fork off a thread to start consuming the output output <- hGetContents outh outMVar <- newEmptyMVar _ <- forkIO $ C.evaluate (length output) >> putMVar outMVar () -- now write and flush any input when (not (null input)) $ do hPutStr inh input; hFlush inh hClose inh -- done with stdin -- wait on the output takeMVar outMVar hClose outh -- wait on the process ex <- waitForProcess pid case ex of ExitSuccess -> return (Right output) ExitFailure r -> return (Left (show r)) -- | Android command to start the view server on a given port startViewServer :: Config -> IO () startViewServer c = do maybeProcess "adb" ["shell","service","call","window","1","i32",show (port c)] "" return () -- | Android command to stop the view server stopViewServer :: IO () stopViewServer = do maybeProcess "adb" ["shell","service","call","window","2"] "" return () -- | Android command to forward a port adbForward :: Config -> IO () adbForward c = do maybeProcess "adb" ["forward", "tcp:" ++ show (port c), "tcp:" ++ show (port c)] "" return () -- | Android command to test if the view server is running -- (the code to parse the result is quick and dirty) isViewServerRunning :: IO Bool isViewServerRunning = do r <- maybeProcess "adb" ["shell","service","call","window","3"] "" either (const $ return False) (const $ return True) $ do mp <- r let nb = read . take 8 . drop 1 . drop 8 . drop 15 $ mp if nb == 1 then Right "" else Left "" -- | When the view server is running, execute the action. whenViewServer :: IO a -> IO () whenViewServer action = do r <- isViewServerRunning if r then do action return () else return () -- adb shell service call window 1 i32 4939 -- adb shell service call window 3 -- adb shell service call window 2 -- adb forward tcp:4939 tcp:4939 -- base/core/java/Android/view/ViewDebug.java -- private static final String REMOTE_COMMAND_CAPTURE = "CAPTURE"; -- private static final String REMOTE_COMMAND_DUMP = "DUMP"; -- private static final String REMOTE_COMMAND_INVALIDATE = "INVALIDATE"; -- private static final String REMOTE_COMMAND_REQUEST_LAYOUT = "REQUEST_LAYOUT"; -- private static final String REMOTE_PROFILE = "PROFILE"; -- private static final String REMOTE_COMMAND_CAPTURE_LAYERS = "CAPTURE_LAYERS"; -- private static final String REMOTE_COMMAND_OUTPUT_DISPLAYLIST = "OUTPUT_DISPLAYLIST"; -- Dump give property:length,value (length is length of value) -- Number of front spaces before the view name are used to define the tree structure of this view with parents -- id = namedProperties.get("mID").value; -- -- left = getInt("mLeft", 0); -- top = getInt("mTop", 0); -- width = getInt("getWidth()", 0); -- height = getInt("getHeight()", 0); -- scrollX = getInt("mScrollX", 0); -- scrollY = getInt("mScrollY", 0); -- paddingLeft = getInt("mPaddingLeft", 0); -- paddingRight = getInt("mPaddingRight", 0); -- paddingTop = getInt("mPaddingTop", 0); -- paddingBottom = getInt("mPaddingBottom", 0); -- marginLeft = getInt("layout_leftMargin", Integer.MIN_VALUE); -- marginRight = getInt("layout_rightMargin", Integer.MIN_VALUE); -- marginTop = getInt("layout_topMargin", Integer.MIN_VALUE); -- marginBottom = getInt("layout_bottomMargin", Integer.MIN_VALUE); -- baseline = getInt("getBaseline()", 0); -- willNotDraw = getBoolean("willNotDraw()", false); -- hasFocus = getBoolean("hasFocus()", false); -- -- hasMargins = marginLeft != Integer.MIN_VALUE && -- marginRight != Integer.MIN_VALUE && -- marginTop != Integer.MIN_VALUE && -- marginBottom != Integer.MIN_VALUE;