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