From bf733475a0651327f04d31cd9ed434dd385b6241 Mon Sep 17 00:00:00 2001 From: Bernhard Urban Date: Sun, 20 May 2012 15:35:31 +0200 Subject: [PATCH] codegen: a few more hacks to get more of classpath running --- Mate/BasicBlocks.hs | 2 ++ Mate/Utilities.hs | 1 + Mate/X86CodeGen.hs | 15 ++++++++++++++- ffi/native.c | 4 ++++ 4 files changed, 21 insertions(+), 1 deletion(-) diff --git a/Mate/BasicBlocks.hs b/Mate/BasicBlocks.hs index 8cd919a..1f393ce 100644 --- a/Mate/BasicBlocks.hs +++ b/Mate/BasicBlocks.hs @@ -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 diff --git a/Mate/Utilities.hs b/Mate/Utilities.hs index 0fd5ddd..211b68f 100644 --- a/Mate/Utilities.hs +++ b/Mate/Utilities.hs @@ -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; diff --git a/Mate/X86CodeGen.hs b/Mate/X86CodeGen.hs index 42ee662..a53e704 100644 --- a/Mate/X86CodeGen.hs +++ b/Mate/X86CodeGen.hs @@ -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 diff --git a/ffi/native.c b/ffi/native.c index a3e877c..99d641c 100644 --- a/ffi/native.c +++ b/ffi/native.c @@ -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; +} -- 2.25.1