main: some kind of argument parsing
authorBernhard Urban <lewurm@gmail.com>
Sun, 20 May 2012 00:10:12 +0000 (02:10 +0200)
committerBernhard Urban <lewurm@gmail.com>
Sun, 20 May 2012 00:10:12 +0000 (02:10 +0200)
o -cp, -classpath and -jar support now from commandline.
  args parsing is a mess, I know. Unfortunately I can't use
  getopt here, because the weird argument syntax of openjdk
  java.
o finally, calls like `./mate tests.Static5' are also possible now
  (before it was `./mate tests/Static5' only)
o new dependency: package split

Mate.hs
Mate/ClassPool.hs
tools/installhaskellenv.sh

diff --git a/Mate.hs b/Mate.hs
index 95daaf8133d890e2445ef353b05072d5aeb9288e..a4e2a97c258b0e8d687db652da39b49fd6b5a9f1 100644 (file)
--- a/Mate.hs
+++ b/Mate.hs
@@ -6,7 +6,7 @@ module Main where
 import System.Environment
 import Data.Char
 import Data.List
-import Data.String.Utils
+import Data.List.Split
 import qualified Data.ByteString.Lazy as B
 
 #ifdef DEBUG
@@ -25,23 +25,39 @@ main ::  IO ()
 main = do
   args <- getArgs
   register_signal
-  addClassPath "./"
-  case args of
-    [clspath] -> do
-      let bclspath = B.pack $ map (fromIntegral . ord) clspath
+  parseArgs args False
+
+parseArgs :: [String] -> Bool -> IO ()
+parseArgs ("-jar":jarpath:_) stdcp = do
+  if not stdcp then addClassPath "./" else return ()
+  addClassPathJAR jarpath
+  res <- readMainClass jarpath
+  case res of
+    Nothing -> error "JAR: no MainClass entry found. Try to pass the jar file via -cp instead."
+    Just mc -> do
+      let bclspath = B.pack $ map (fromIntegral . ord) mc
       cls <- getClassFile bclspath
       executeMain bclspath cls
-    ["-jar", jarpath] -> do
-      addClassPathJAR jarpath
-      res <- readMainClass jarpath
-      case res of
-        Nothing -> error "JAR: no MainClass entry found. Try to pass the jar file via -cp instead."
-        Just mc -> do
-          let mc' = replace "." "/" mc
-          let bclspath = B.pack $ map (fromIntegral . ord) mc'
-          cls <- getClassFile bclspath
-          executeMain bclspath cls
-    _ -> error "Usage: mate [<class-file> | -jar <jar-file>]"
+parseArgs ("-cp":cps) cpset = parseArgs ("-classpath":cps) cpset
+parseArgs ("-classpath":cps:xs) False = do
+  let paths = splitOn ":" cps
+  mapM_ addStuff paths
+  parseArgs xs True
+  where
+  addStuff :: String -> IO ()
+  addStuff x
+    | ".jar" `isSuffixOf` x = addClassPathJAR x
+    | otherwise = addClassPath $ x ++ "/"
+parseArgs ("-classpath":xs) _ = parseArgs ("-":xs) True -- usage
+parseArgs (('-':_):_) _ = error "Usage: mate [-cp|-classpath <cp1:cp2:..>] [<class-file> | -jar <jar-file>]"
+-- first argument which isn't prefixed by '-' should be a class file
+parseArgs (clspath:_) stdcp = do
+  if not stdcp then addClassPath "./" else return ()
+  let bclspath = B.pack $ map (fromIntegral . ord) clspath
+  cls <- getClassFile bclspath
+  executeMain bclspath cls
+parseArgs _ _ = parseArgs ["-"] False
+
 
 executeMain :: B.ByteString -> Class Direct -> IO ()
 executeMain bclspath cls = do
index 0844ea5efa3e96f7655517a20ac59ad4ead29241..d9e965c3cacc7085d9ec44d47404f0ecb49def86 100644 (file)
@@ -21,6 +21,7 @@ import Data.Binary
 import qualified Data.Map as M
 import qualified Data.Set as S
 import qualified Data.ByteString.Lazy as B
+import Data.String.Utils
 import Control.Monad
 
 #ifdef DEBUG
@@ -267,17 +268,20 @@ loadAndInitClass path = do
 
 
 readClassFile :: String -> IO (Class Direct)
-readClassFile path = readIORef classPaths >>= rcf
+readClassFile path' = readIORef classPaths >>= rcf
   where
+  path = replace "." "/" path'
   rcf :: [MClassPath] -> IO (Class Direct)
   rcf [] = error $ "readClassFile: Class \"" ++ (show path) ++ "\" not found."
   rcf ((Directory pre):xs) = do
     let cf = pre ++ path ++ ".class"
+    printfCp "rcf: searching @ %s for %s\n" (show pre) (show path)
     b <- doesFileExist cf
     if b
       then parseClassFile cf
       else rcf xs
   rcf ((JAR p):xs) = do
+    printfCp "rcf: searching %s in JAR\n" (show path)
     entry <- getEntry p path
     case entry of
       Just (LoadedJAR _ cls) -> return cls
index 159d2528641a805019eba535ef0e64ac73487198..6bfb63af8a97a6be6434f14c870dafad587a8d51 100755 (executable)
@@ -8,6 +8,7 @@ cabal update
 cabal install missingh --enable-shared
 cabal install heap --enable-shared
 cabal install plugins --enable-shared
+cabal install split --enable-shared
 
 git clone git://wien.tomnetworks.com/disassembler.git
 cd disassembler