debug: get rid of #ifdef guards
[mate.git] / Mate / MethodPool.hs
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE ForeignFunctionInterface #-}
4 #include "debug.h"
5 module Mate.MethodPool where
6
7 import Data.Binary
8 import Data.String.Utils
9 import qualified Data.Map as M
10 import qualified Data.Set as S
11 import qualified Data.ByteString.Lazy as B
12 import System.Plugins
13
14 import Foreign.Ptr
15 import Foreign.C.Types
16 import Foreign.C.String
17
18 import JVM.ClassFile
19
20 import Harpy
21 import Harpy.X86Disassembler
22
23 #ifdef DEBUG
24 import Text.Printf
25 #endif
26
27 import Mate.BasicBlocks
28 import Mate.Types
29 import Mate.X86CodeGen
30 import Mate.Utilities
31 import Mate.ClassPool
32 import Mate.Debug
33
34 foreign import ccall "dynamic"
35    code_void :: FunPtr (IO ()) -> (IO ())
36
37 foreign export ccall getTrapType :: CUInt -> CUInt -> IO CUInt
38 getTrapType :: CUInt -> CUInt -> IO CUInt
39 getTrapType signal_from from2 = do
40   tmap <- get_trapmap >>= ptr2trapmap
41   case M.lookup (fromIntegral signal_from) tmap of
42     (Just (MI _)) -> return 0
43     (Just (VI _)) -> return 1
44     (Just (SFI _)) -> return 2
45     (Just (II _)) -> return 4
46     -- maybe we've a hit on the second `from' value
47     Nothing -> case M.lookup (fromIntegral from2) tmap of
48       (Just (VI _)) -> return 1
49       (Just (II _)) -> return 4
50       (Just _) -> error $ "getTrapType: abort #1 :-("
51       Nothing -> error $ "getTrapType: abort #2 :-("
52
53 foreign export ccall getMethodEntry :: CUInt -> CUInt -> IO CUInt
54 getMethodEntry :: CUInt -> CUInt -> IO CUInt
55 getMethodEntry signal_from methodtable = do
56   mmap <- get_methodmap >>= ptr2methodmap
57   tmap <- get_trapmap >>= ptr2trapmap
58   vmap <- get_virtualmap >>= ptr2virtualmap
59
60   let w32_from = fromIntegral signal_from
61   let mi = tmap M.! w32_from
62   let mi'@(MethodInfo method cm sig) =
63         case mi of
64           (MI x) -> x
65           (VI (MethodInfo methname _ msig)) ->
66               (MethodInfo methname (vmap M.! (fromIntegral methodtable)) msig)
67           (II (MethodInfo methname _ msig)) ->
68               (MethodInfo methname (vmap M.! (fromIntegral methodtable)) msig)
69           _ -> error $ "getMethodEntry: no trapInfo. abort."
70   case M.lookup mi' mmap of
71     Nothing -> do
72       cls <- getClassFile cm
73       printf_mp "getMethodEntry(from 0x%08x): no method \"%s\" found. compile it\n" w32_from (show mi')
74       mm <- lookupMethodRecursive method [] cls
75       case mm of
76         Just (mm', clsnames, cls') -> do
77             let flags = methodAccessFlags mm'
78             case S.member ACC_NATIVE flags of
79               False -> do
80                 hmap <- parseMethod cls' method
81                 case hmap of
82                   Just hmap' -> do
83                     entry <- compileBB hmap' (MethodInfo method (thisClass cls') sig)
84                     addMethodRef entry mi' clsnames
85                     return $ fromIntegral entry
86                   Nothing -> error $ (show method) ++ " not found. abort"
87               True -> do
88                 -- TODO(bernhard): cleaner please... *do'h*
89                 let symbol = (replace "/" "_" $ toString cm) ++ "__" ++ (toString method) ++ "__" ++ (replace ";" "_" $ replace "/" "_" $ replace "(" "_" (replace ")" "_" $ toString $ encode sig))
90                 printf_mp "native-call: symbol: %s\n" symbol
91                 nf <- loadNativeFunction symbol
92                 let w32_nf = fromIntegral nf
93                 let mmap' = M.insert mi' w32_nf mmap
94                 methodmap2ptr mmap' >>= set_methodmap
95                 return nf
96         Nothing -> error $ (show method) ++ " not found. abort"
97     Just w32 -> return (fromIntegral w32)
98
99 lookupMethodRecursive :: B.ByteString -> [B.ByteString] -> Class Resolved
100                          -> IO (Maybe ((Method Resolved, [B.ByteString], Class Resolved)))
101 lookupMethodRecursive name clsnames cls = do
102   case res of
103     Just x -> return $ Just (x, nextclsn, cls)
104     Nothing -> if thisname == "java/lang/Object"
105       then return $ Nothing
106       else do
107         supercl <- getClassFile (superClass cls)
108         lookupMethodRecursive name nextclsn supercl
109   where
110   res = lookupMethod name cls
111   thisname = thisClass cls
112   nextclsn :: [B.ByteString]
113   nextclsn = thisname:clsnames
114
115 -- TODO(bernhard): UBERHAX.  ghc patch?
116 foreign import ccall safe "lookupSymbol"
117    c_lookupSymbol :: CString -> IO (Ptr a)
118
119 loadNativeFunction :: String -> IO (CUInt)
120 loadNativeFunction sym = do
121         _ <- loadRawObject "ffi/native.o"
122         -- TODO(bernhard): WTF
123         resolveObjs (return ())
124         ptr <- withCString sym c_lookupSymbol
125         if (ptr == nullPtr)
126           then error $ "dyn. loading of \"" ++ sym ++ "\" failed."
127           else return $ fromIntegral $ ptrToIntPtr ptr
128
129 -- t_01 :: IO ()
130 -- t_01 = do
131 --   (entry, _) <- testCase "./tests/Fib.class" "fib"
132 --   let int_entry = ((fromIntegral $ ptrToIntPtr entry) :: Word32)
133 --   let mmap = M.insert ("fib" :: String) int_entry M.empty
134 --   mapM_ (\(x,y) -> printf "%s at 0x%08x\n" x y) $ M.toList mmap
135 --   mmap2ptr mmap >>= set_mmap
136 --   demo_mmap -- access Data.Map from C
137
138 initMethodPool :: IO ()
139 initMethodPool = do
140   methodmap2ptr M.empty >>= set_methodmap
141   trapmap2ptr M.empty >>= set_trapmap
142   classmap2ptr M.empty >>= set_classmap
143   virtualmap2ptr M.empty >>= set_virtualmap
144   stringsmap2ptr M.empty >>= set_stringsmap
145   interfacesmap2ptr M.empty >>= set_interfacesmap
146   interfacemethodmap2ptr M.empty >>= set_interfacemethodmap
147
148
149 addMethodRef :: Word32 -> MethodInfo -> [B.ByteString] -> IO ()
150 addMethodRef entry (MethodInfo mmname _ msig) clsnames = do
151   mmap <- get_methodmap >>= ptr2methodmap
152   let newmap = M.fromList $ map (\x -> ((MethodInfo mmname x msig), entry)) clsnames
153   methodmap2ptr (mmap `M.union` newmap) >>= set_methodmap
154
155
156 compileBB :: MapBB -> MethodInfo -> IO Word32
157 compileBB hmap methodinfo = do
158   tmap <- get_trapmap >>= ptr2trapmap
159
160   cls <- getClassFile (methClassName methodinfo)
161   let ebb = emitFromBB (methName methodinfo) cls hmap
162   (_, Right right) <- runCodeGen ebb () ()
163
164   let ((entry, _, _, new_tmap), _) = right
165   let tmap' = M.union tmap new_tmap -- prefers elements in cmap
166   trapmap2ptr tmap' >>= set_trapmap
167
168   printf_jit "generated code of \"%s\":\n" (toString $ methName methodinfo)
169   mapM_ (printf_jit "%s\n" . showAtt) (snd right)
170   printf_jit "\n\n"
171   -- UNCOMMENT NEXT LINE FOR GDB FUN
172   -- _ <- getLine
173   -- (1) start it with `gdb ./mate' and then `run <classfile>'
174   -- (2) on getLine, press ctrl+c
175   -- (3) `br *0x<addr>'; obtain the address from the disasm above
176   -- (4) `cont' and press enter
177   return $ fromIntegral $ ptrToIntPtr entry
178
179
180 executeFuncPtr :: Word32 -> IO ()
181 executeFuncPtr entry =
182   code_void $ ((castPtrToFunPtr $ intPtrToPtr $ fromIntegral entry) :: FunPtr (IO ()))