44e0545cf599980a17c72779009b6bdc068e301c
[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.ClassPool
31 import Mate.Debug
32 import Mate.Utilities
33
34 foreign import ccall "dynamic"
35    code_void :: FunPtr (IO ()) -> IO ()
36
37
38 getMethodEntry :: CUInt -> CUInt -> IO CUInt
39 getMethodEntry signal_from methodtable = do
40   mmap <- getMethodMap
41   tmap <- getTrapMap
42   vmap <- getVirtualMap
43
44   let w32_from = fromIntegral signal_from
45   let mi = tmap M.! w32_from
46   let mi'@(MethodInfo method cm sig) =
47         case mi of
48           (MI x) -> x
49           (VI  _(MethodInfo methname _ msig)) ->
50               MethodInfo methname (vmap M.! fromIntegral methodtable) msig
51           (II _ (MethodInfo methname _ msig)) ->
52               MethodInfo methname (vmap M.! fromIntegral methodtable) msig
53           _ -> error "getMethodEntry: no trapInfo. abort."
54   setTrapMap $ M.delete w32_from tmap
55   case M.lookup mi' mmap of
56     Nothing -> do
57       cls <- getClassFile cm
58       printfMp "getMethodEntry(from 0x%08x): no method \"%s\" found. compile it\n" w32_from (show mi')
59       mm <- lookupMethodRecursive method sig [] cls
60       case mm of
61         Just (mm', clsnames, cls') -> do
62             let flags = methodAccessFlags mm'
63             if S.member ACC_NATIVE flags
64               then do
65                 -- TODO(bernhard): cleaner please... *do'h*
66                 let sym1 = replace "/" "_" $ toString cm
67                     parenth = replace "(" "_" $ replace ")" "_" $ toString $ encode sig
68                     sym2 = replace ";" "_" $ replace "/" "_" parenth
69                     symbol = sym1 ++ "__" ++ toString method ++ "__" ++ sym2
70                 printfMp "native-call: symbol: %s\n" symbol
71                 nf <- loadNativeFunction symbol
72                 let w32_nf = fromIntegral nf
73                 setMethodMap $ M.insert mi' w32_nf mmap
74                 return nf
75               else do
76                 hmap <- parseMethod cls' method sig
77                 case hmap of
78                   Just hmap' -> do
79                     entry <- compileBB hmap' (MethodInfo method (thisClass cls') sig)
80                     addMethodRef entry mi' clsnames
81                     return $ fromIntegral entry
82                   Nothing -> error $ show method ++ " not found. abort"
83         Nothing -> error $ show method ++ " not found. abort"
84     Just w32 -> return (fromIntegral w32)
85
86 lookupMethodRecursive :: B.ByteString -> MethodSignature -> [B.ByteString] -> Class Direct
87                          -> IO (Maybe (Method Direct, [B.ByteString], Class Direct))
88 lookupMethodRecursive name sig clsnames cls =
89   case res of
90     Just x -> return $ Just (x, nextclsn, cls)
91     Nothing -> if thisname == "java/lang/Object"
92       then return Nothing
93       else do
94         supercl <- getClassFile (superClass cls)
95         lookupMethodRecursive name sig nextclsn supercl
96   where
97   res = lookupMethodSig name sig cls
98   thisname = thisClass cls
99   nextclsn :: [B.ByteString]
100   nextclsn = thisname:clsnames
101
102 -- TODO(bernhard): UBERHAX.  ghc patch?
103 foreign import ccall safe "lookupSymbol"
104    c_lookupSymbol :: CString -> IO (Ptr a)
105
106 loadNativeFunction :: String -> IO CUInt
107 loadNativeFunction sym = do
108         _ <- loadRawObject "ffi/native.o"
109         -- TODO(bernhard): WTF
110         resolveObjs (return ())
111         ptr <- withCString sym c_lookupSymbol
112         if ptr == nullPtr
113           then error $ "dyn. loading of \"" ++ sym ++ "\" failed."
114           else return $ fromIntegral $ ptrToIntPtr ptr
115
116 -- t_01 :: IO ()
117 -- t_01 = do
118 --   (entry, _) <- testCase "./tests/Fib.class" "fib"
119 --   let int_entry = ((fromIntegral $ ptrToIntPtr entry) :: Word32)
120 --   let mmap = M.insert ("fib" :: String) int_entry M.empty
121 --   mapM_ (\(x,y) -> printf "%s at 0x%08x\n" x y) $ M.toList mmap
122 --   mmap2ptr mmap >>= set_mmap
123 --   demo_mmap -- access Data.Map from C
124
125 addMethodRef :: Word32 -> MethodInfo -> [B.ByteString] -> IO ()
126 addMethodRef entry (MethodInfo mmname _ msig) clsnames = do
127   mmap <- getMethodMap
128   let newmap = M.fromList $ map (\x -> (MethodInfo mmname x msig, entry)) clsnames
129   setMethodMap $ mmap `M.union` newmap
130
131
132 compileBB :: MapBB -> MethodInfo -> IO Word32
133 compileBB hmap methodinfo = do
134   tmap <- getTrapMap
135
136   cls <- getClassFile (methClassName methodinfo)
137   let ebb = emitFromBB (methName methodinfo) (methSignature methodinfo) cls hmap
138   (_, Right right) <- runCodeGen ebb () ()
139
140   let ((entry, _, _, new_tmap), _) = right
141   setTrapMap $ tmap `M.union` new_tmap -- prefers elements in tmap
142
143   printfJit "generated code of \"%s\" from \"%s\":\n" (toString $ methName methodinfo) (toString $ methClassName methodinfo)
144   mapM_ (printfJit "%s\n" . showAtt) (snd right)
145   printfJit "\n\n"
146   -- UNCOMMENT NEXT LINES FOR GDB FUN
147   --if (toString $ methName methodinfo) == "thejavamethodIwant2debug"
148   --  then getLine
149   --  else return "foo"
150   -- (1) start it with `gdb ./mate' and then `run <classfile>'
151   -- (2) on getLine, press ctrl+c
152   -- (3) `br *0x<addr>'; obtain the address from the disasm above
153   -- (4) `cont' and press enter
154   return $ fromIntegral $ ptrToIntPtr entry
155
156
157 executeFuncPtr :: Word32 -> IO ()
158 executeFuncPtr entry =
159   code_void ((castPtrToFunPtr $ intPtrToPtr $ fromIntegral entry) :: FunPtr (IO ()))