Enhace constants pool handling.
[hs-java.git] / JVM / Common.hs
index 7271e469eabf7cb603af0c54c92125aea4f4c427..422cc8b88b3a7562861c9ca63c64401c730b1fa9 100644 (file)
@@ -1,19 +1,28 @@
 {-# LANGUAGE TypeFamilies, StandaloneDeriving, FlexibleInstances, FlexibleContexts, UndecidableInstances #-}
--- | This module declares `high-level' data types for Java classes, methods etc.
-module JVM.Common where
+-- | This module declares some commonly used functions and instances.
+module JVM.Common
+  (toCharList,
+  poolSize,
+  (!),
+  showListIx,
+  mapFindIndex,
+  byteString
+  ) where
 
-import Codec.Binary.UTF8.String hiding (encode, decode)
 import Data.Binary
 import Data.Binary.Put
 import qualified Data.ByteString.Lazy as B
-import Data.Char
-import Data.String
 import qualified Data.Map as M
+import Data.Default
+import Data.List
 
 import JVM.ClassFile
 
-instance IsString B.ByteString where
-  fromString s = B.pack $ map (fromIntegral . ord) $ encodeString s
+instance Default B.ByteString where
+  def = B.empty
+
+instance Default Word16 where
+  def = 0
 
 toCharList :: B.ByteString -> [Int]
 toCharList bstr = map fromIntegral $ B.unpack bstr
@@ -24,10 +33,16 @@ poolSize = M.size
 (!) :: (Ord k) => M.Map k a -> k -> a
 (!) = (M.!)
 
-showListIx :: (Show a) => [a] -> String
-showListIx list = unlines $ zipWith s [1..] list
-  where s i x = show i ++ ":\t" ++ show x
+showListIx :: (Show i, Show a) => [(i,a)] -> String
+showListIx list = unlines $ map s list
+  where s (i, x) = show i ++ ":\t" ++ show x
 
 byteString ::  (Binary t) => t -> B.ByteString
 byteString x = runPut (put x)
 
+mapFindIndex :: (Num k) => (v -> Bool) -> M.Map k v -> Maybe k
+mapFindIndex check m =
+  case find (check . snd) (M.assocs m) of
+    Nothing -> Nothing
+    Just (k,_) -> Just k
+