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