{- | Android View Hierarchy importer -} module Main( -- * Android View Hierarchy Importer -- $doc main ) where {-# LANGUAGE OverloadedStrings #-} import Adb import ViewServer import Control.Monad(when) import qualified Data.ByteString.Char8 as B import Data.Tree(drawTree,Tree(..)) import Output import Types import System.Console.CmdTheLine import Control.Applicative import Data.Maybe(isJust,fromJust) termInfo :: TermInfo termInfo = def { termName = "AndroidViewHierarchyImporter", version = "1.0" } -- | Print the string with the configuration. -- Depending on the confuration the result will either go -- to stdout or into a file printWithOutputFile :: Config -> String -> IO () printWithOutputFile c s | isJust (outputFile c) = do writeFile (fromJust . outputFile $ c) s | otherwise = putStr s -- | Convert a view to a string drawView :: (Int,(String,View)) -> IO String drawView (_,(name,view)) = return $ name ++ "\n" ++ show view ++ "\n" -- | Display the view hierarchy using the right format dumpWindow config windowHash = do let lViews = listViews config windowHash case (outputFormat config) of Raw -> rawViews config windowHash >>= printWithOutputFile config Views -> lViews >>= mapM drawView >>= return . concat >>= printWithOutputFile config Graphviz -> do v <- lViews let t = mkTree v printWithOutputFile config $ graphviz (fmap viewName t) Opml -> do v <- lViews let t = mkTree v printWithOutputFile config $ opml t -- | Connect to the view server connectWith config = do r <- isViewServerRunning when (forward config) $ do adbForward config when (not r) $ do startViewServer config whenViewServer $ do when ((mustListWindows config) && not (isJust (mustListViews config))) $ do l <- listWindows config print l maybe (return ()) (dumpWindow config) $ (mustListViews config) stopViewServer return () -- | Do we want to dump a window windowOption :: Term (Maybe WindowHash) windowOption = opt Nothing $ (optInfo ["windowhash", "w"]) { argDoc = "Window hash" , argName = "windowhash" } -- | Format of the output outputFormatOption :: Term OutputFormat outputFormatOption = opt Opml $ (optInfo ["format","f"]) { argDoc = "Output format for the view list" , argName = "raw / view / graphviz / opml"} -- | Do we want an output file or do we use stdout outputFileOption :: Term (Maybe FilePath) outputFileOption = opt Nothing $ (optInfo ["output","o"]) { argDoc = "Output file or stdout if nothing" , argName = "filepath" } -- | Do we disable adb port forwarding (required with a board) doNotForwardOption :: Term Bool doNotForwardOption = flag $ (optInfo ["donotforward"]) {argDoc = "Do not forward the port"} -- | Port to use for the view server -- (you can telnet to this port) portOption :: Term Int portOption = opt 4939 $ (optInfo ["portid", "p"]) { argDoc = "Port ID" , argName = "integer" } -- | Hostname for the view server hostOption :: Term String hostOption = opt "127.0.0.1" $ (optInfo ["host", "h"]) { argDoc = "Host" , argName = "IP or hostname" } -- | Option processing term :: Term (IO ()) term = connectWith <$> config where changeWindowOption :: Maybe WindowHash -> Config -> Config changeWindowOption s c = c {mustListViews = s} changeOutputFormat :: OutputFormat -> Config -> Config changeOutputFormat s c = c {outputFormat = s} changeOutputFile :: Maybe FilePath -> Config -> Config changeOutputFile s c = c {outputFile = s} changeForwardOption :: Bool -> Config -> Config changeForwardOption s c = c {forward = s} changePortOption :: Int -> Config -> Config changePortOption s c = c {port = s} changeHostOption :: String -> Config -> Config changeHostOption s c = c {hostname = s} config = liftA2 changeHostOption hostOption . liftA2 changePortOption portOption . liftA2 changeForwardOption doNotForwardOption . liftA2 changeOutputFile outputFileOption . liftA2 changeOutputFormat outputFormatOption . liftA2 changeWindowOption windowOption $ pure defaultConfig main :: IO () main = run ( term, termInfo ) {- $doc This command line tool will connect to an Android device (real or virtual), start the view server and dump view hierarchies. It needs much more testing. The view server is requiring a development board or an Android Virtual Device. If you're on a final product, you may have to root your device to enable the view server. So, by default this tool is configured to communicate with a local AVD. It has not yet been tested with a board. Here are some examples of how to use it: @ AndroidViewHierarchyImporter @ This command will connect to abd and forward the abd port (required when an AVD is used to be able to map the AVD port to a port of the computer). Then, the command will launch the view server and list the windows on the plaform. A window for this tool is defined as an hash (generated by the view server) and the activity name. If you want to dump the view hierarchy of a window, use the tool with a different option @ AndroidViewHierarchyImporter -w b57b5078 @ The -w option is using the hash of a window to dump its hierarchy. Note that it is very slow to dump a view hierarchy. And it may not always work. For instance, on Jelly Bean, I have attempted to dump the hierarchy of the Image Wallpaper and either it is failing or it is taking too much time for my patience. It is not a problem with this tool. The same behavior can be observed by telneting to the view server and sending the right commands. The dump format is OPML with by default only the width, height and layer type for the view. If you want more info in the OPML you'll have to modify the source code of this tool ! But, if you want all the infos, you can use different output formats like raw and view @ AndroidViewHierarchyImporter -w b57b5078 -f raw @ Thus previous command is just dumping the result of the view server without any processing. @ AndroidViewHierarchyImporter -w b57b5078 -f view @ The previous command is parsing the result of the view server and is resulting view datatypes. @ AndroidViewHierarchyImporter -w b57b5078 -f graphviz @ The previous command is generating a graphviz file containing only shortened names for the views (only the class name without the package and an hexadecimal number identifying the object). @ AndroidViewHierarchyImporter --help @ The previous command is listing all options. -}