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