debug: get rid of #ifdef guards
[mate.git] / Mate / MethodPool.hs
index 85010eb9d11677545db7a30e3832477fbee9e700..067a9898585acdd9b2ecca60c3df6ae7841c2b14 100644 (file)
@@ -1,6 +1,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
+#include "debug.h"
 module Mate.MethodPool where
 
 import Data.Binary
@@ -17,9 +18,9 @@ import Foreign.C.String
 import JVM.ClassFile
 
 import Harpy
-#ifdef DEBUG
 import Harpy.X86Disassembler
 
+#ifdef DEBUG
 import Text.Printf
 #endif
 
@@ -28,7 +29,7 @@ import Mate.Types
 import Mate.X86CodeGen
 import Mate.Utilities
 import Mate.ClassPool
-
+import Mate.Debug
 
 foreign import ccall "dynamic"
    code_void :: FunPtr (IO ()) -> (IO ())
@@ -69,9 +70,7 @@ getMethodEntry signal_from methodtable = do
   case M.lookup mi' mmap of
     Nothing -> do
       cls <- getClassFile cm
-#ifdef DEBUG
-      printf "getMethodEntry(from 0x%08x): no method \"%s\" found. compile it\n" w32_from (show mi')
-#endif
+      printf_mp "getMethodEntry(from 0x%08x): no method \"%s\" found. compile it\n" w32_from (show mi')
       mm <- lookupMethodRecursive method [] cls
       case mm of
         Just (mm', clsnames, cls') -> do
@@ -88,9 +87,7 @@ getMethodEntry signal_from methodtable = do
               True -> do
                 -- TODO(bernhard): cleaner please... *do'h*
                 let symbol = (replace "/" "_" $ toString cm) ++ "__" ++ (toString method) ++ "__" ++ (replace ";" "_" $ replace "/" "_" $ replace "(" "_" (replace ")" "_" $ toString $ encode sig))
-#ifdef DEBUG
-                printf "native-call: symbol: %s\n" symbol
-#endif
+                printf_mp "native-call: symbol: %s\n" symbol
                 nf <- loadNativeFunction symbol
                 let w32_nf = fromIntegral nf
                 let mmap' = M.insert mi' w32_nf mmap
@@ -168,10 +165,9 @@ compileBB hmap methodinfo = do
   let tmap' = M.union tmap new_tmap -- prefers elements in cmap
   trapmap2ptr tmap' >>= set_trapmap
 
-#ifdef DEBUG
-  printf "disasm:\n"
-  mapM_ (putStrLn . showAtt) (snd right)
-#endif
+  printf_jit "generated code of \"%s\":\n" (toString $ methName methodinfo)
+  mapM_ (printf_jit "%s\n" . showAtt) (snd right)
+  printf_jit "\n\n"
   -- UNCOMMENT NEXT LINE FOR GDB FUN
   -- _ <- getLine
   -- (1) start it with `gdb ./mate' and then `run <classfile>'