codegen: {put,get}static for static field access
authorBernhard Urban <lewurm@gmail.com>
Mon, 23 Apr 2012 14:10:21 +0000 (16:10 +0200)
committerBernhard Urban <lewurm@gmail.com>
Mon, 23 Apr 2012 14:12:15 +0000 (16:12 +0200)
TODO:
- execute static initializer upon first loading
- inheritance

Makefile
Mate.hs
Mate/ClassPool.hs
Mate/MethodPool.hs
Mate/Types.hs
Mate/Utilities.hs
Mate/X86CodeGen.hs
ffi/trap.c
tests/Static1.java
tests/Static2.java [new file with mode: 0644]

index 6fdae5590af42d1174e8ea8fc29f6ff9c9ad12ee..82ff90a2e5834a41d6ed93363be044defcb84fba 100644 (file)
--- a/Makefile
+++ b/Makefile
@@ -28,7 +28,10 @@ test: mate $(CLASS_FILES)
        @printf "should be:  0x%08x\n" 8
        @printf "should be:  0x%08x\n" 13
        ./$< tests/Native1 | egrep -i -e '^printsomething: '
-       ./$< tests/Static1
+       ./$< tests/Static1 | grep mainresult
+       @printf "should be:  0x%08x\n" 0x33
+       ./$< tests/Static2 | grep mainresult
+       @printf "should be:  0x%08x\n" 0x55
 
 %.class: %.java
        $(JAVAC) $<
diff --git a/Mate.hs b/Mate.hs
index 8e63fbf578132bd2c3afeeeae57700583c3fccd8..946b6921893c0f32dce67c3010f7bbcd1350b041 100644 (file)
--- a/Mate.hs
+++ b/Mate.hs
@@ -3,14 +3,12 @@ module Main where
 
 import System.Environment
 import Data.Char
-import Data.String.Utils
 import Data.List
 import qualified Data.ByteString.Lazy as B
 
 import Text.Printf
 
 import JVM.ClassFile
-import JVM.Converter
 import JVM.Dump
 
 import Mate.BasicBlocks
index ccfe1b3afc7b4bad72e817e09479582cfacc0bc3..eb97e211c9f4c54859353e327df7cef654b58570 100644 (file)
@@ -2,41 +2,71 @@
 {-# LANGUAGE ForeignFunctionInterface #-}
 module Mate.ClassPool where
 
-import Data.Binary
-import Data.String.Utils
 import qualified Data.Map as M
 import qualified Data.Set as S
 import qualified Data.ByteString.Lazy as B
-import System.Plugins
 
 import Text.Printf
 
 import Foreign.Ptr
 import Foreign.C.Types
-import Foreign.C.String
-import Foreign.StablePtr
 import Foreign.Marshal.Alloc
 
 import JVM.ClassFile
 import JVM.Converter
 
-import Harpy
-import Harpy.X86Disassembler
-
-import Mate.BasicBlocks
 import Mate.Types
-import Mate.Utilities
 
+getClassInfo :: B.ByteString -> IO ClassInfo
+getClassInfo path = do
+  ptr_classmap <- get_classmap
+  class_map <- ptr2classmap ptr_classmap
+  case M.lookup path class_map of
+    Nothing -> loadClass path
+    Just ci -> return ci
 
 getClassFile :: B.ByteString -> IO (Class Resolved)
 getClassFile path = do
+  (ClassInfo _ cfile _ _) <- getClassInfo path
+  return cfile
+
+getFieldBase :: B.ByteString -> IO (CUInt)
+getFieldBase path = do
+  (ClassInfo _ _ fs _) <- getClassInfo path
+  return $ fromIntegral $ ptrToIntPtr fs
+
+getFieldOffset :: B.ByteString -> B.ByteString -> IO (CUInt)
+getFieldOffset path field = do
+  (ClassInfo _ _ _ fieldmap) <- getClassInfo path
+  return $ fromIntegral $ fieldmap M.! field
+
+foreign export ccall getFieldAddr :: CUInt -> Ptr () -> IO CUInt
+getFieldAddr :: CUInt -> Ptr () -> IO CUInt
+getFieldAddr from ptr_trapmap = do
+  trapmap <- ptr2tmap ptr_trapmap
+  let w32_from = fromIntegral from
+  let sfi = trapmap M.! w32_from
+  case sfi of
+    (SFI (StaticFieldInfo cls field)) -> do
+      off <- getFieldOffset cls field
+      base <- getFieldBase cls
+      return $ base + off
+    _ -> error $ "getFieldAddr: no trapInfo. abort"
+
+loadClass :: B.ByteString -> IO ClassInfo
+loadClass path = do
   ptr_classmap <- get_classmap
   class_map <- ptr2classmap ptr_classmap
-  case M.lookup path class_map of
-    Nothing -> do
-      let rpath = toString $ path `B.append` ".class"
-      cfile <- parseClassFile rpath
-      let class_map' = M.insert path (ClassInfo path cfile) class_map
-      classmap2ptr class_map' >>= set_classmap
-      return cfile
-    Just (ClassInfo name cfs) -> return cfs
+  let rpath = toString $ path `B.append` ".class"
+  cfile <- parseClassFile rpath
+  printf "class fieldlength: %d\n" $ classFieldsCount cfile
+  -- TODO(bernhard): correct sizes. int only atm
+  let filteredfields = filter (S.member ACC_STATIC . fieldAccessFlags) (classFields cfile)
+  let fm = zipWith (\x y -> (fieldName y, x)) [0,4..] filteredfields
+  let fieldmap = M.fromList fm
+  fieldbase <- mallocBytes ((fromIntegral $ M.size fieldmap) * 4)
+  putStrLn $ "fieldmap: " ++ (show fieldmap)
+  let new_ci = ClassInfo path cfile fieldbase fieldmap
+  let class_map' = M.insert path new_ci class_map
+  classmap2ptr class_map' >>= set_classmap
+  return new_ci
index 1d744932883ea84f69fd70ec38efff188322063e..aff4dfede03cec0038df0bf51b03de6cd3c361bd 100644 (file)
@@ -6,7 +6,6 @@ import Data.Binary
 import Data.String.Utils
 import qualified Data.Map as M
 import qualified Data.Set as S
-import qualified Data.ByteString.Lazy as B
 import System.Plugins
 
 import Text.Printf
@@ -14,10 +13,8 @@ import Text.Printf
 import Foreign.Ptr
 import Foreign.C.Types
 import Foreign.C.String
-import Foreign.StablePtr
 
 import JVM.ClassFile
-import JVM.Converter
 
 import Harpy
 import Harpy.X86Disassembler
@@ -84,7 +81,7 @@ loadNativeFunction sym = do
         ptr <- withCString sym c_lookupSymbol
         if (ptr == nullPtr)
           then error $ "dyn. loading of \"" ++ sym ++ "\" failed."
-          else return $ fromIntegral $ minusPtr ptr nullPtr
+          else return $ fromIntegral $ ptrToIntPtr ptr
 
 -- t_01 :: IO ()
 -- t_01 = do
index 832160e0a7f176e0b8763958110b3429cd1a5fd7..69180847de5bc8f16f6e8c894a42d24bf5c5afd9 100644 (file)
@@ -4,13 +4,12 @@ module Mate.Types where
 
 import Data.Char
 import Data.Word
+import Data.Int
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
 import Codec.Binary.UTF8.String hiding (encode,decode)
 
 import Foreign.Ptr
-import Foreign.C.Types
-import Foreign.C.String
 import Foreign.StablePtr
 
 import JVM.ClassFile
@@ -36,7 +35,8 @@ type TMap = M.Map Word32 TrapInfo
 data TrapInfo = MI MethodInfo | SFI StaticFieldInfo
 
 data StaticFieldInfo = StaticFieldInfo {
-  dunnoyet :: Int }
+  sfiClassName :: B.ByteString,
+  sfiFieldName :: B.ByteString }
 
 -- B.ByteString = name of method
 -- Word32 = entrypoint of method
@@ -44,9 +44,13 @@ type MMap = M.Map MethodInfo Word32
 
 type ClassMap = M.Map B.ByteString ClassInfo
 
+type FieldMap = M.Map B.ByteString Int32
+
 data ClassInfo = ClassInfo {
   clName :: B.ByteString,
-  clFile :: Class Resolved }
+  clFile :: Class Resolved,
+  clField :: Ptr Int32,
+  clFieldMap :: FieldMap }
 
 data MethodInfo = MethodInfo {
   methName :: B.ByteString,
index 54d32d30db2bf7fcd4d46a468ae0727c835f2dc8..2d755ccf4c3385f6ceeec382e184c99ce6abafb2 100644 (file)
@@ -24,6 +24,10 @@ buildMethodID cls idx = MethodInfo (ntName nt) rc (ntSignature nt)
   where
   (CMethod rc nt) = (constsPool cls) M.! idx
 
+buildFieldID :: Class Resolved -> Word16 -> StaticFieldInfo
+buildFieldID cls idx = StaticFieldInfo rc (ntName fnt)
+  where (CField rc fnt) = (constsPool cls) M.! idx
+
 methodGetArgsCount :: Class Resolved -> Word16 -> Word32
 methodGetArgsCount cls idx = fromIntegral $ length args
   where
index ccaee0eef77a3676542021a44138afd723a88b70..0891d546459f947007ccbf12bb8d3faf49a9f0fa 100644 (file)
@@ -17,7 +17,6 @@ import Text.Printf
 import qualified JVM.Assembler as J
 import JVM.Assembler hiding (Instruction)
 import JVM.ClassFile
-import JVM.Converter
 
 import Harpy
 import Harpy.X86Disassembler
@@ -173,6 +172,22 @@ emitFromBB cls hmap =  do
         -- push result on stack if method has a return value
         when (methodHaveReturnValue cls cpidx) (push eax)
         return $ Just $ (w32_calladdr, MI l)
+    emit' (PUTSTATIC cpidx) = do
+        pop eax
+        ep <- getEntryPoint
+        let w32_ep = (fromIntegral $ ptrToIntPtr ep) :: Word32
+        trapaddr <- getCodeOffset
+        let w32_trapaddr = w32_ep + (fromIntegral trapaddr)
+        mov (Addr 0x00000000) eax -- it's a trap
+        return $ Just $ (w32_trapaddr, SFI $ buildFieldID cls cpidx)
+    emit' (GETSTATIC cpidx) = do
+        ep <- getEntryPoint
+        let w32_ep = (fromIntegral $ ptrToIntPtr ep) :: Word32
+        trapaddr <- getCodeOffset
+        let w32_trapaddr = w32_ep + (fromIntegral trapaddr)
+        mov eax (Addr 0x00000000) -- it's a trap
+        push eax
+        return $ Just $ (w32_trapaddr, SFI $ buildFieldID cls cpidx)
     emit' insn = emit insn >> return Nothing
 
     emit :: J.Instruction -> CodeGen e s ()
index 14a8034d10324d0ca38279629b8f5e302ce88f3f..10354f83f32d9911e2f1ef7e9ceea9ac6492dcf4 100644 (file)
@@ -17,6 +17,7 @@
 #include <asm/ucontext.h>
 
 unsigned int getMethodEntry(unsigned int, void *, void *);
+unsigned int getFieldAddr(unsigned int, void*);
 
 #define NEW_MAP(prefix) \
        void* prefix ## _map = NULL; \
@@ -64,13 +65,37 @@ void callertrap(int nSignal, siginfo_t *info, void *ctx)
        // while (1) ;
 }
 
+void staticfieldtrap(int nSignal, siginfo_t *info, void *ctx)
+{
+       struct ucontext *uctx = (struct ucontext *) ctx;
+       unsigned int from = (unsigned int) uctx->uc_mcontext.eip;
+       unsigned int patchme = getFieldAddr(from, trap_map);
+       unsigned int *to_patch = (unsigned int *) (from + 2);
+
+       printf("staticfieldtrap by 0x%08x\n", from);
+       printf(" to_patch: 0x%08x\n", (unsigned int) to_patch);
+       printf("*to_patch: 0x%08x\n", *to_patch);
+       if (*to_patch != 0x00000000) {
+               printf("something is wrong here. abort\n");
+               exit(0);
+       }
+       *to_patch = patchme;
+       printf("*to_patch: 0x%08x\n", *to_patch);
+}
+
 void register_signal(void)
 {
+       struct sigaction illaction;
+       illaction.sa_sigaction = callertrap;
+       sigemptyset(&illaction.sa_mask);
+       illaction.sa_flags = SA_SIGINFO | SA_RESTART;
+       sigaction(SIGILL, &illaction, NULL);
+
        struct sigaction segvaction;
-       segvaction.sa_sigaction = callertrap;
+       segvaction.sa_sigaction = staticfieldtrap;
        sigemptyset(&segvaction.sa_mask);
        segvaction.sa_flags = SA_SIGINFO | SA_RESTART;
-       sigaction(SIGILL, &segvaction, NULL);
+       sigaction(SIGSEGV, &segvaction, NULL);
 }
 
 unsigned int getaddr(void)
index 56bd3938a69e033b32f6cca7a2a997d7f18e126a..726da7dfad3d251bc87fb2749ca189b3b4145966 100644 (file)
@@ -1,20 +1,16 @@
 package tests;
 
 public class Static1 {
-       public static int a;
-       public static int b;
-
-       static {
-               Static1.a = 0x1337;
-       }
+       public static int x;
+       public static int y;
 
        public static void main(String []args) {
-               Static1.a = 0x11;
-               Static1.b = 0x22;
+               Static1.x = 0x11;
+               Static1.y = 0x22;
                addnumbers();
        }
 
        public static int addnumbers() {
-               return Static1.a + Static1.b;
+               return Static1.x + Static1.y;
        }
 }
diff --git a/tests/Static2.java b/tests/Static2.java
new file mode 100644 (file)
index 0000000..874360d
--- /dev/null
@@ -0,0 +1,16 @@
+package tests;
+
+public class Static2 {
+       public static int a;
+       public static int b;
+
+       public static void main(String []args) {
+               Static2.a = 0x55;
+               Static2.b = 0x11;
+               // force different {put,get}index for Static1.{x,y}
+               // in Static2 as in Static1
+               Static1.x = 0x33;
+               Static1.y = 0x22;
+               Static1.addnumbers();
+       }
+}