methodpool: small demo how to access a Data.Map instance from C
[mate.git] / Mate / MethodPool.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE ForeignFunctionInterface #-}
3 module Mate.MethodPool where
4
5 import Data.Binary
6 import Data.Int
7 import Data.List
8 import Data.Maybe
9 import qualified Data.Map as M
10 import qualified Data.ByteString.Lazy as B
11
12 import Foreign
13 import Foreign.Ptr
14 import Foreign.StablePtr
15 import Foreign.C.Types
16 import Foreign.C.String
17
18 import Text.Printf
19
20 import qualified JVM.Assembler as J
21 import JVM.Assembler hiding (Instruction)
22
23 import Harpy
24 import Harpy.X86Disassembler
25
26 import Mate.X86CodeGen
27
28
29 foreign import ccall "get_mmap"
30   get_mmap :: IO (Ptr ())
31
32 foreign import ccall "set_mmap"
33   set_mmap :: Ptr () -> IO ()
34
35 foreign import ccall "demo_mmap"
36   demo_mmap :: IO ()
37
38
39 type MMap = M.Map String Word32
40
41 foreign export ccall getMethodEntry :: Ptr () -> CString -> IO CUInt
42 getMethodEntry :: Ptr () -> CString -> IO CUInt
43 getMethodEntry ptr_mmap cstr = do
44   mmap <- deRefStablePtr $ ((castPtrToStablePtr ptr_mmap) :: StablePtr MMap)
45   k <- peekCString cstr
46   case M.lookup k mmap of
47     Nothing -> return 0
48     Just w32 -> return (fromIntegral w32)
49
50 t_01 = do
51   (entry, end) <- testCase "./tests/Fib.class" "fib"
52   let int_entry = ((fromIntegral $ ptrToIntPtr entry) :: Word32)
53   let mmap = M.insert ("fib" :: String) int_entry M.empty
54   mapM_ (\(x,y) -> printf "%s at 0x%08x\n" x y) $ M.toList mmap
55   ptr_mmap <- newStablePtr mmap
56   set_mmap $ castStablePtrToPtr ptr_mmap
57   demo_mmap -- access Data.Map from C