debug: remove #ifdef's and use dumb logger
[mate.git] / Mate / MethodPool.hs
index c8cb0848499f9ab74c4b1b828397c218b7037107..223f50909fc6d04f62167be770392f7d21e00aa2 100644 (file)
@@ -1,7 +1,5 @@
-{-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
-#include "debug.h"
 module Mate.MethodPool where
 
 import Data.Binary
@@ -18,13 +16,7 @@ import Foreign.C.String
 import JVM.ClassFile
 
 import Harpy
-#ifdef DBG_JIT
 import Harpy.X86Disassembler
-#endif
-
-#ifdef DEBUG
-import Text.Printf
-#endif
 
 import Mate.BasicBlocks
 import Mate.Types
@@ -32,10 +24,19 @@ import Mate.NativeMachine
 import Mate.ClassPool
 import Mate.Debug
 import Mate.Utilities
+import Mate.Rts()
 
 foreign import ccall "dynamic"
    code_void :: FunPtr (IO ()) -> IO ()
 
+foreign import ccall "&printMemoryUsage"
+  printMemoryUsageAddr :: FunPtr (IO ())
+foreign import ccall "&loadLibrary"
+  loadLibraryAddr :: FunPtr (IO ())
+
+foreign import ccall "&printGCStats"
+  printGCStatsAddr :: FunPtr (IO ())
 
 getMethodEntry :: CPtrdiff -> CPtrdiff -> IO CPtrdiff
 getMethodEntry signal_from methodtable = do
@@ -48,8 +49,7 @@ getMethodEntry signal_from methodtable = do
   let mi'@(MethodInfo method cm sig) =
        case mi of
          (StaticMethod x) -> x
-         (VirtualMethod   _ (MethodInfo methname _ msig)) -> newMi methname msig
-         (InterfaceMethod _ (MethodInfo methname _ msig)) -> newMi methname msig
+         (VirtualCall _ (MethodInfo methname _ msig) _) -> newMi methname msig
          _ -> error "getMethodEntry: no TrapCause found. abort."
        where newMi mn = MethodInfo mn (vmap M.! fromIntegral methodtable)
   -- bernhard (TODO): doesn't work with gnu classpath at some point. didn't
@@ -59,22 +59,34 @@ getMethodEntry signal_from methodtable = do
   entryaddr <- case M.lookup mi' mmap of
     Nothing -> do
       cls <- getClassFile cm
-      printfMp "getMethodEntry(from 0x%08x): no method \"%s\" found. compile it\n" w32_from (show mi')
+      printfMp $ printf "getMethodEntry(from 0x%08x): no method \"%s\" found. compile it\n" w32_from (show mi')
       mm <- lookupMethodRecursive method sig [] cls
       case mm of
         Just (mm', clsnames, cls') -> do
             let flags = methodAccessFlags mm'
             if S.member ACC_NATIVE flags
               then do
-                -- TODO(bernhard): cleaner please... *do'h*
-                let sym1 = replace "/" "_" $ toString cm
-                    parenth = replace "(" "_" $ replace ")" "_" $ toString $ encode sig
-                    sym2 = replace ";" "_" $ replace "/" "_" parenth
-                    symbol = sym1 ++ "__" ++ toString method ++ "__" ++ sym2
-                printfMp "native-call: symbol: %s\n" symbol
-                nf <- loadNativeFunction symbol
-                setMethodMap $ M.insert mi' nf mmap
-                return nf
+                let scm = toString cm; smethod = toString method
+                if scm == "jmate/lang/MateRuntime" then do
+                  case smethod of
+                    "loadLibrary" ->
+                       return . funPtrToAddr $ loadLibraryAddr
+                    "printGCStats" ->
+                       return . funPtrToAddr $ printGCStatsAddr
+                    "printMemoryUsage" ->
+                       return . funPtrToAddr $ printMemoryUsageAddr
+                    _ ->
+                       error $ "native-call: " ++ smethod ++ " not found."
+                else do
+                  -- TODO(bernhard): cleaner please... *do'h*
+                  let sym1 = replace "/" "_" scm
+                      parenth = replace "(" "_" $ replace ")" "_" $ toString $ encode sig
+                      sym2 = replace ";" "_" $ replace "/" "_" parenth
+                      symbol = sym1 ++ "__" ++ smethod ++ "__" ++ sym2
+                  printfMp $ printf "native-call: symbol: %s\n" symbol
+                  nf <- loadNativeFunction symbol
+                  setMethodMap $ M.insert mi' nf mmap
+                  return nf
               else do
                 rawmethod <- parseMethod cls' method sig
                 entry <- compileBB rawmethod (MethodInfo method (thisClass cls') sig)
@@ -84,6 +96,9 @@ getMethodEntry signal_from methodtable = do
     Just w32 -> return w32
   return $ fromIntegral entryaddr
 
+funPtrToAddr :: Num b => FunPtr a -> b
+funPtrToAddr = fromIntegral . ptrToIntPtr . castFunPtrToPtr
+
 lookupMethodRecursive :: B.ByteString -> MethodSignature -> [B.ByteString] -> Class Direct
                          -> IO (Maybe (Method Direct, [B.ByteString], Class Direct))
 lookupMethodRecursive name sig clsnames cls =
@@ -136,17 +151,18 @@ compileBB rawmethod methodinfo = do
 
   cls <- getClassFile (methClassName methodinfo)
   let ebb = emitFromBB cls rawmethod
-  (_, Right right) <- runCodeGen ebb () ()
+  let cgconfig = defaultCodeGenConfig { codeBufferSize = fromIntegral $ (rawCodeLength rawmethod) * 32 }
+  (_, Right right) <- runCodeGenWithConfig ebb () () cgconfig
 
   let ((entry, _, _, new_tmap), _) = right
   setTrapMap $ tmap `M.union` new_tmap -- prefers elements in tmap
 
-  printfJit "generated code of \"%s\" from \"%s\":\n" (toString $ methName methodinfo) (toString $ methClassName methodinfo)
-  printfJit "\tstacksize: 0x%04x, locals: 0x%04x\n" (rawStackSize rawmethod) (rawLocals rawmethod)
-#ifdef DBG_JIT
-  mapM_ (printfJit "%s\n" . showAtt) (snd right)
-#endif
-  printfJit "\n\n"
+  printfJit $ printf "generated code of \"%s\" from \"%s\":\n" (toString $ methName methodinfo) (toString $ methClassName methodinfo)
+  printfJit $ printf "\tstacksize: 0x%04x, locals: 0x%04x\n" (rawStackSize rawmethod) (rawLocals rawmethod)
+  if mateDEBUG
+    then mapM_ (printfJit . printf "%s\n" . showAtt) (snd right)
+    else return ()
+  printfJit $ printf "\n\n"
   -- UNCOMMENT NEXT LINES FOR GDB FUN
   -- if (toString $ methName methodinfo) == "thejavamethodIwant2debug"
   --   then putStrLn "press CTRL+C now for setting a breakpoint. then `c' and ENTER for continue" >> getLine