playing around with generated codebuffers
authorBernhard Urban <lewurm@gmail.com>
Sat, 17 Mar 2012 20:20:39 +0000 (21:20 +0100)
committerBernhard Urban <lewurm@gmail.com>
Sat, 17 Mar 2012 20:20:39 +0000 (21:20 +0100)
be aware, generated code doesn't make sense yet ;-)

Mate.hs

diff --git a/Mate.hs b/Mate.hs
index 9fe09c6e3068b0da6d3baec792e4551a190af6f7..60eef34ea8114df6aedfc453f2bd14ea3fb08f30 100644 (file)
--- a/Mate.hs
+++ b/Mate.hs
@@ -1,5 +1,6 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE TemplateHaskell, FlexibleInstances #-}
+{-# LANGUAGE ForeignFunctionInterface #-}
 module Main where
 
 import Data.Binary
@@ -20,11 +21,17 @@ import JVM.Converter
 import JVM.Dump
 
 import Foreign
+import Foreign.Ptr
+import Foreign.C.Types
 
 import Harpy
 import Harpy.X86Disassembler
 
 
+foreign import ccall "dynamic"
+   code_void :: FunPtr (CInt -> IO CInt) -> (CInt -> IO CInt)
+
+
 $(callDecl "callAsWord32" [t|Word32|])
 
 main = do
@@ -52,12 +59,24 @@ main = do
 
 runstuff :: Ptr Int32 -> B.ByteString -> IO ()
 runstuff env bytecode = do
-          (_, Right (ret, disasm)) <- runCodeGen (compile $ codeInstructions $ decodeMethod bytecode) env ()
-          printf "return value: 0x%08x\n" ret
+          let emittedcode = compile $ codeInstructions $ decodeMethod bytecode
+          (_, Right (entryPtr, disasm)) <- runCodeGen emittedcode env ()
+          printf "entry point: 0x%08x\n" ((fromIntegral $ ptrToIntPtr entryPtr) :: Int)
+
+          let entryFuncPtr = ((castPtrToFunPtr entryPtr) :: FunPtr (CInt -> IO CInt))
+          result <- code_void entryFuncPtr (fromIntegral 0x1337)
+          let iresult::Int; iresult = fromIntegral result
+          printf "result: 0x%08x\n" iresult
+
+          result2 <- code_void entryFuncPtr (fromIntegral (-0x20))
+          let iresult2::Int; iresult2 = fromIntegral result2
+          printf "result: 0x%08x\n" iresult2
+
           printf "disasm:\n"
           mapM_ (putStrLn . showAtt) disasm
           return ()
 
+
 entryCode :: CodeGen e s ()
 entryCode = do push ebp
                mov ebp esp
@@ -67,18 +86,18 @@ exitCode = do mov esp ebp
               pop ebp
               ret
 
-compile :: [J.Instruction] -> CodeGen (Ptr Int32) s (Int32, [Instruction])
+compile :: [J.Instruction] -> CodeGen (Ptr Int32) s (Ptr Word8, [Instruction])
 compile insn = do
   entryCode
   mapM compile_ins insn
   exitCode
   d <- disassemble
-  r <- callAsWord32
-  return (fromIntegral r, d)
+  c <- getEntryPoint
+  return (c,d)
 
 compile_ins :: J.Instruction -> CodeGen (Ptr Int32) s ()
 compile_ins (BIPUSH w8) = do mov eax ((fromIntegral w8) :: Word32)
-compile_ins (PUTSTATIC w16) = do nop
+compile_ins (PUTSTATIC w16) = do add eax (Disp 8, ebp) -- add first argument to %eax
 compile_ins (GETSTATIC w16) = do nop
 compile_ins ICONST_2 = do nop
 compile_ins IMUL = do nop