nativeMachine: use constants
[mate.git] / Mate / ClassPool.hs
index e476c8b5b92d47b05ff0f2c7a1c0c38b95766915..e6c5bfef8d333b2650755be78844b47021ff8809 100644 (file)
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ForeignFunctionInterface #-}
 #include "debug.h"
 module Mate.ClassPool (
   getClassInfo,
@@ -20,6 +19,7 @@ import Data.Word
 import Data.Binary
 import qualified Data.Map as M
 import qualified Data.Set as S
+import Data.List
 import qualified Data.ByteString.Lazy as B
 import Data.String.Utils
 import Control.Monad
@@ -49,6 +49,7 @@ import {-# SOURCE #-} Mate.MethodPool
 import Mate.Types
 import Mate.Debug
 import Mate.GarbageAlloc
+import Mate.NativeSizes
 
 getClassInfo :: B.ByteString -> IO ClassInfo
 getClassInfo path = do
@@ -62,7 +63,7 @@ getClassFile path = do
   ci <- getClassInfo path
   return $ ciFile ci
 
-getStaticFieldOffset :: B.ByteString -> B.ByteString -> IO CUInt
+getStaticFieldOffset :: B.ByteString -> B.ByteString -> IO CPtrdiff
 getStaticFieldOffset path field = do
   ci <- getClassInfo path
   return $ fromIntegral $ ciStaticMap ci M.! field
@@ -76,8 +77,8 @@ getFieldOffset path field = do
 getMethodOffset :: B.ByteString -> B.ByteString -> IO Word32
 getMethodOffset path method = do
   ci <- getClassInfo path
-  -- (4+) one slot for "interface-table-ptr"
-  return $ (+4) $ fromIntegral $ ciMethodMap ci M.! method
+  -- (+ ptrSize) one slot for "interface-table-ptr"
+  return $ (+ ptrSize) $ fromIntegral $ ciMethodMap ci M.! method
 
 getMethodTable :: B.ByteString -> IO Word32
 getMethodTable path = do
@@ -90,17 +91,17 @@ getObjectSize path = do
   -- TODO(bernhard): correct sizes for different types...
   let fsize = fromIntegral $ M.size $ ciFieldMap ci
   -- one slot for "method-table-ptr"
-  return $ (1 + fsize) * 4
+  return $ (1 + fsize) * ptrSize
 
-getStaticFieldAddr :: CUInt -> IO CUInt
+getStaticFieldAddr :: CPtrdiff -> IO CPtrdiff
 getStaticFieldAddr from = do
   trapmap <- getTrapMap
   let w32_from = fromIntegral from
   let sfi = trapmap M.! w32_from
   setTrapMap $ M.delete w32_from trapmap
   case sfi of
-    (SFI (StaticFieldInfo cls field)) -> getStaticFieldOffset cls field
-    _ -> error "getFieldAddr: no trapInfo. abort"
+    (StaticField (StaticFieldInfo cls field)) -> getStaticFieldOffset cls field
+    _ -> error "getFieldAddr: no TrapCause found. abort"
 
 -- interface + method + signature plz!
 getInterfaceMethodOffset :: B.ByteString -> B.ByteString -> B.ByteString -> IO Word32
@@ -189,41 +190,34 @@ loadInterface path = do
       setInterfaceMethodMap $ M.fromList sm `M.union` M.fromList mm `M.union` immap
       setInterfaceMap $ M.insert path cfile imap'
   where
-  zipbase base = zipWith (\x y -> (entry y, x + base)) [0,4..]
-  entry = getname path
-  getname p y = p `B.append` methodName y `B.append` encode (methodSignature y)
+    zipbase base = zipWith (\x y -> (entry y, x + base)) [0,4..]
+    entry = getname path
+    getname p y = p `B.append` methodName y `B.append` encode (methodSignature y)
 
 
 calculateFields :: Class Direct -> Maybe ClassInfo -> IO (FieldMap, FieldMap)
 calculateFields cf superclass = do
     -- TODO(bernhard): correct sizes. int only atm
 
-    -- TODO(bernhard): nicer replacement for `myspan'
-    let (sfields, ifields) = myspan (S.member ACC_STATIC . fieldAccessFlags) (classFields cf)
-        myspan :: (a -> Bool) -> [a] -> ([a], [a])
-        myspan _ [] = ([],[])
-        myspan p (x:xs)
-          | p x = (x:ns, ni)
-          | otherwise = (ns, x:ni)
-          where (ns,ni) = myspan p xs
+    let (sfields, ifields) = partition (S.member ACC_STATIC . fieldAccessFlags) (classFields cf)
 
-    staticbase <- mallocClassData $ fromIntegral (length sfields) * 4
-    let i_sb = fromIntegral $ ptrToIntPtr staticbase
-    let sm = zipbase i_sb sfields
     let sc_sm = getsupermap superclass ciStaticMap
+    staticbase <- mallocClassData $ fromIntegral (length sfields) * 4
+    let sm = zipbase (fromIntegral $ ptrToIntPtr staticbase) sfields
     -- new fields "overwrite" old ones, if they have the same name
-    let staticmap = M.fromList sm `M.union` sc_sm
+    let staticmap = sm `M.union` sc_sm
 
     let sc_im = getsupermap superclass ciFieldMap
     -- "+ 4" for the method table pointer
     let max_off = (4+) $ fromIntegral $ M.size sc_im * 4
     let im = zipbase max_off ifields
     -- new fields "overwrite" old ones, if they have the same name
-    let fieldmap = M.fromList im `M.union` sc_im
+    let fieldmap = im `M.union` sc_im
 
     return (staticmap, fieldmap)
   where
-  zipbase base = zipWith (\x y -> (fieldName y, x + base)) [0,4..]
+    zipbase :: Int32 -> [Field Direct] -> FieldMap
+    zipbase base = foldr (\(x,y) -> M.insert (fieldName y) (x + base)) M.empty . zip [0,4..]
 
 -- helper
 getsupermap :: Maybe ClassInfo -> (ClassInfo -> FieldMap) -> FieldMap
@@ -261,16 +255,13 @@ loadAndInitClass path = do
   -- execute class initializer
   case lookupMethod "<clinit>" (ciFile ci) of
     Just m -> do
-      hmap <- parseMethod (ciFile ci) "<clinit>" $ MethodSignature [] ReturnsVoid
-      case hmap of
-        Just hmap' -> do
-          let mi = MethodInfo "<clinit>" path (methodSignature m)
-          entry <- compileBB hmap' mi
-          addMethodRef entry mi [path]
-          printfCp "executing static initializer from %s now\n" (toString path)
-          executeFuncPtr entry
-          printfCp "static initializer from %s done\n" (toString path)
-        Nothing -> error "readClass: static initializer not found (WTF?). abort"
+      rawmethod <- parseMethod (ciFile ci) "<clinit>" $ MethodSignature [] ReturnsVoid
+      let mi = MethodInfo "<clinit>" path (methodSignature m)
+      entry <- compileBB rawmethod mi
+      addMethodRef entry mi [path]
+      printfCp "executing static initializer from %s now\n" (toString path)
+      executeFuncPtr entry
+      printfCp "static initializer from %s done\n" (toString path)
     Nothing -> return ()
 
   class_map' <- getClassMap
@@ -282,23 +273,23 @@ loadAndInitClass path = do
 readClassFile :: String -> IO (Class Direct)
 readClassFile path' = readIORef classPaths >>= rcf
   where
-  path = replace "." "/" path'
-  rcf :: [MClassPath] -> IO (Class Direct)
-  rcf [] = error $ "readClassFile: Class \"" ++ (show path) ++ "\" not found."
-  rcf ((Directory pre):xs) = do
-    let cf = pre ++ path ++ ".class"
-    printfCp "rcf: searching @ %s for %s\n" (show pre) (show path)
-    b <- doesFileExist cf
-    if b
-      then parseClassFile cf
-      else rcf xs
-  rcf ((JAR p):xs) = do
-    printfCp "rcf: searching %s in JAR\n" (show path)
-    entry <- getEntry p path
-    case entry of
-      Just (LoadedJAR _ cls) -> return cls
-      Nothing -> rcf xs
-      _ -> error $ "readClassFile: Class \"" ++ show path ++ "\" in JAR not found. #1"
+    path = replace "." "/" path'
+    rcf :: [MClassPath] -> IO (Class Direct)
+    rcf [] = error $ "readClassFile: Class \"" ++ show path ++ "\" not found."
+    rcf (Directory pre:xs) = do
+      let cf = pre ++ path ++ ".class"
+      printfCp "rcf: searching @ %s for %s\n" (show pre) (show path)
+      b <- doesFileExist cf
+      if b
+        then parseClassFile cf
+        else rcf xs
+    rcf (JAR p:xs) = do
+      printfCp "rcf: searching %s in JAR\n" (show path)
+      entry <- getEntry p path
+      case entry of
+        Just (LoadedJAR _ cls) -> return cls
+        Nothing -> rcf xs
+        _ -> error $ "readClassFile: Class \"" ++ show path ++ "\" in JAR not found. #1"
 
 data MClassPath =
   Directory String |