Created
April 8, 2013 04:18
-
-
Save LeifWarner/5334215 to your computer and use it in GitHub Desktop.
Read Java method signatures from haskell
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE OverloadedStrings, FlexibleContexts #-} | |
import Control.Monad.Exception | |
import qualified Data.ByteString.Lazy as B | |
import Data.ByteString.Lazy.Char8 (pack) | |
import System.Environment (getArgs) | |
import JVM.ClassFile | |
import JVM.Assembler | |
import JVM.Builder | |
import JVM.Exceptions | |
import Java.ClassPath | |
args :: MethodSignature -> [ArgumentSignature] | |
args (MethodSignature a _) = a | |
ret :: MethodSignature -> ReturnSignature | |
ret (MethodSignature _ r) = r | |
copy :: (Throws ENotFound e, Throws ENotLoaded e, Throws UnexpectedEndMethod e) => | |
String -> B.ByteString -> GenerateIO e () | |
copy klass meth = do | |
-- Add current directory (with Hello.class) to ClassPath | |
withClassPath $ addDirectory "." | |
-- Load method signature: Hello.hello() from Hello.class | |
helloJava <- getClassMethod klass meth | |
let sig = ntSignature helloJava | |
--newMethod [ACC_PUBLIC, ACC_STATIC] "hello" [undefined] (undefined) $ do | |
newMethod [ACC_PUBLIC, ACC_STATIC] meth (args sig) (ret sig) $ do | |
setStackSize 1 | |
i0 RETURN | |
return () | |
printSig :: String -> String -> IO () | |
printSig klass meth = do | |
copiedClass <- generateIO [] "Test" (copy ("./" ++ klass) (pack meth)) | |
let methSig = methodSignature $ head $ classMethods $ copiedClass | |
putStrLn $ "Args: " ++ (show $ args methSig) | |
putStrLn $ "Returns: " ++ (show $ ret methSig) | |
main :: IO () | |
main = do | |
argv <- getArgs | |
case argv of | |
[klass, meth] -> printSig klass meth | |
_ -> putStrLn "Usage: JavaSig className methodName" |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment