gc: factor out allocation
[mate.git] / Mate / Strings.hs
index 2867bad5a9c7dd6500604d02d9dee0ff7029f72e..6e541814e7645247ee0f2a638d61fe7cd4a31aab 100644 (file)
@@ -1,5 +1,7 @@
+{-# LANGUAGE CPP #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ForeignFunctionInterface #-}
+#include "debug.h"
 module Mate.Strings (
   getUniqueStringAddr
   ) where
@@ -8,13 +10,17 @@ import Data.Word
 import qualified Data.Map as M
 import qualified Data.ByteString.Lazy as B
 import qualified Data.ByteString.Internal as BI
+#ifdef DEBUG
 import Text.Printf
+#endif
 
 import Foreign.Ptr
-import Foreign.ForeignPtr
+import Foreign.Marshal.Utils
 import Foreign.Marshal.Array
 
 import Mate.Types
+import Mate.Debug
+import Mate.GarbageAlloc
 
 
 getUniqueStringAddr :: B.ByteString -> IO Word32
@@ -28,14 +34,15 @@ getUniqueStringAddr str = do
       return addr
     Just addr -> return addr
 
--- TOOD(bernhard): quite hackish
 allocateJavaString :: B.ByteString -> IO Word32
 allocateJavaString str = do
+  -- TODO(bernhard): is this also true for UTF8 stuff?
   let strlen = fromIntegral $ B.length str
-  let str_unpacked = (map fromIntegral $ B.unpack str) :: [Word8]
-  arr <- newArray str_unpacked
-  newstr <- BI.create strlen (\x -> BI.memcpy x arr (fromIntegral strlen))
-  let (newstrptr, _, _) = BI.toForeignPtr newstr
-  let w32_ptr = fromIntegral $ ptrToIntPtr $ unsafeForeignPtrToPtr newstrptr
-  printf "new str ptr: 0x%08x\n" w32_ptr
+  arr <- newArray $ ((map fromIntegral $ B.unpack str) :: [Word8])
+  -- (+1) for \0
+  newstr <- mallocString (strlen + 1)
+  BI.memset newstr 0 (fromIntegral $ strlen + 1)
+  copyBytes newstr arr strlen
+  let w32_ptr = fromIntegral $ ptrToIntPtr newstr
+  printf_str "new str ptr: 0x%08x (%s)@%d\n" w32_ptr (toString str) strlen
   return w32_ptr