codegen: a few more hacks to get more of classpath running
authorBernhard Urban <lewurm@gmail.com>
Sun, 20 May 2012 13:35:31 +0000 (15:35 +0200)
committerBernhard Urban <lewurm@gmail.com>
Sun, 20 May 2012 19:53:13 +0000 (21:53 +0200)
Mate/BasicBlocks.hs
Mate/Utilities.hs
Mate/X86CodeGen.hs
ffi/native.c

index 8cd919a1e4f770152d971295ca4e7e2712477f07..1f393ce52d28b828abcf2155070ed4aa467d6c50 100644 (file)
@@ -195,6 +195,8 @@ calculateInstructionOffset = cio' (0, Nothing)
       IF _ w16 -> twotargets w16
       IF_ICMP _ w16 -> twotargets w16
       IF_ACMP _ w16 -> twotargets w16
+      IFNONNULL w16 -> twotargets w16
+      IFNULL w16 -> twotargets w16
       GOTO w16 -> onetarget w16
       IRETURN -> notarget
       ARETURN -> notarget
index 0fd5ddd74ca9f33c5c313c67c102f03e2c9a077c..211b68f2f5ab2019633b880863db206e84fb61b6 100644 (file)
@@ -43,6 +43,7 @@ methodGetArgsCount cls idx = fromIntegral $ length args
 methodHaveReturnValue :: Class Direct -> Word16 -> Bool
 methodHaveReturnValue cls idx = case ret of
     ReturnsVoid -> False;
+    (Returns BoolType) -> True
     (Returns IntType) -> True;
     (Returns (Array _ _)) -> True
     (Returns (ObjectType _)) -> True;
index 42ee6620232fd4450b81157db8fbf4e0b739906d..a53e704c3cd3ced6ba4b5fba4d83751f0f6560b5 100644 (file)
@@ -4,7 +4,7 @@
 #include "debug.h"
 module Mate.X86CodeGen where
 
-import Prelude hiding (and)
+import Prelude hiding (and, div)
 import Data.Binary
 import Data.BinaryState
 import Data.Int
@@ -29,6 +29,10 @@ import Mate.Types
 import Mate.Utilities
 import Mate.ClassPool
 import Mate.Strings
+import Mate.Debug
+#ifdef DEBUG
+import Text.Printf
+#endif
 
 
 foreign import ccall "dynamic"
@@ -175,6 +179,7 @@ emitFromBB method sig cls hmap =  do
     emit :: J.Instruction -> CodeGen e s ()
     emit POP = add esp (4 :: Word32) -- drop value
     emit DUP = push (Disp 0, esp)
+    emit DUP_X1 = do pop eax; pop ebx; push eax; push ebx; push eax
     emit AASTORE = emit IASTORE
     emit IASTORE = do
         pop eax -- value
@@ -231,12 +236,15 @@ emitFromBB method sig cls hmap =  do
         mtable <- liftIO $ getMethodTable objname
         mov (Disp 0, eax) mtable
     emit (CHECKCAST _) = nop -- TODO(bernhard): ...
+    emit ATHROW = nop -- TODO(bernhard): ...
     emit I2C = do
       pop eax
       and eax (0x000000ff :: Word32)
       push eax
     emit (BIPUSH val) = push (fromIntegral val :: Word32)
     emit (SIPUSH val) = push (fromIntegral (fromIntegral val :: Int16) :: Word32)
+    emit ACONST_NULL = push (0 :: Word32)
+    emit (ICONST_M1) = push ((-1) :: Word32)
     emit (ICONST_0) = push (0 :: Word32)
     emit (ICONST_1) = push (1 :: Word32)
     emit (ICONST_2) = push (2 :: Word32)
@@ -273,10 +281,15 @@ emitFromBB method sig cls hmap =  do
     emit IADD = do pop ebx; pop eax; add eax ebx; push eax
     emit ISUB = do pop ebx; pop eax; sub eax ebx; push eax
     emit IMUL = do pop ebx; pop eax; mul ebx; push eax
+    emit IDIV = do pop ebx; pop eax; div ebx; push eax
+    emit IREM = do pop ebx; pop eax; div ebx; push edx
     emit IXOR = do pop ebx; pop eax; xor eax ebx; push eax
+    emit INEG = do pop eax; neg eax; push eax
     emit (IINC x imm) =
         add (Disp (cArgs x), ebp) (s8_w32 imm)
 
+    emit (IFNONNULL x) = emit (IF C_NE x)
+    emit (IFNULL x) = emit (IF C_EQ x)
     emit (IF_ACMP cond x) = emit (IF_ICMP cond x)
     emit (IF_ICMP cond _) = do
         pop eax -- value2
index a3e877c0d5c8d958759cd372941e17b1606e6639..99d641c5934f55eea5202759df966ea736e01335 100644 (file)
@@ -102,3 +102,7 @@ void java_io_PrintStream__printf_5___Ljava_lang_String_Ljava_lang_Object_Ljava_l
 {
        printf(&fmt->value->str, a1->value, a2->value, a3->value, a4->value, a5->value);
 }
+
+void gnu_classpath_VMSystemProperties__preInit___Ljava_util_Properties__V() {
+       return;
+}