Use Data.Map.Map instead of Data.Array.Array for constants pool.
[hs-java.git] / JVM / Types.hs
index b64da9337dc0216c0c3a7f516d0743fea77dfa70..7ce6580c7140dc0531d4a5c86f9a37182b191226 100644 (file)
@@ -4,11 +4,9 @@ module JVM.Types where
 
 import Codec.Binary.UTF8.String hiding (encode, decode)
 import Control.Applicative
-import Data.Array
 import Data.Binary
 import Data.Binary.Put
 import qualified Data.ByteString.Lazy as B
-import Data.Word
 import Data.Char
 import Data.String
 import qualified Data.Set as S
@@ -22,11 +20,17 @@ instance IsString B.ByteString where
 toString :: B.ByteString -> String
 toString bstr = decodeString $ map (chr . fromIntegral) $ B.unpack bstr
 
+toCharList :: B.ByteString -> [Int]
+toCharList bstr = map fromIntegral $ B.unpack bstr
+
 -- | Constant pool
-type Pool = Array Word16 Constant
+type Pool = M.Map Word16 Constant
+
+poolSize :: Pool -> Int
+poolSize = M.size
 
-asize :: (Ix i) => Array i e -> Int
-asize = length . elems
+(!) :: (Ord k) => M.Map k a -> k -> a
+(!) = (M.!)
 
 showListIx :: (Show a) => [a] -> String
 showListIx list = unlines $ zipWith s [1..] list