Use Data.Map.Map instead of Data.Array.Array for constants pool.
[hs-java.git] / JVM / Assembler.hs
index cc886ae807f50d59fd830a18bf46c9e4684b63e2..31e00fea6ff1678c86bed9e76ef8cd10d7c962a3 100644 (file)
@@ -9,16 +9,19 @@ module JVM.Assembler
    CodeException (..),
    Code (..),
    IMM (..),
-   CMP (..)
+   CMP (..),
+   encodeInstructions,
+   encodeMethod,
+   decodeMethod
   )
   where
 
 import Control.Monad
 import Control.Applicative
+import Data.Ix (inRange)
 import Data.Word
 import qualified Data.Binary as Binary
 import qualified Data.ByteString.Lazy as B
-import Data.Array
 
 import Data.BinaryState
 import JVM.ClassFile
@@ -273,7 +276,7 @@ data Instruction =
   | JSR_W Word32           -- ^ 201
   deriving (Eq, Show)
 
--- ^ JVM array type (primitive types)
+-- | JVM array type (primitive types)
 data ArrayType =
     T_BOOLEAN  -- ^ 4
   | T_CHAR     -- ^ 5
@@ -285,14 +288,14 @@ data ArrayType =
   | T_LONG     -- ^ 11
   deriving (Eq, Show, Enum)
 
--- ^ Parse opcode with immediate constant
+-- | Parse opcode with immediate constant
 imm :: Word8                   -- ^ Base opcode
     -> (IMM -> Instruction)    -- ^ Instruction constructor
     -> Word8                   -- ^ Opcode to parse
     -> GetState s Instruction
 imm base constr x = return $ constr $ toEnum $ fromIntegral (x-base)
 
--- ^ Put opcode with immediate constant
+-- | Put opcode with immediate constant
 putImm :: Word8                -- ^ Base opcode
        -> IMM                  -- ^ Constant to add to opcode
        -> PutState Integer ()
@@ -326,7 +329,7 @@ instance BinaryState Integer ArrayType where
 
   put t = putByte (atype2byte t)
 
--- ^ Put opcode with one argument
+-- | Put opcode with one argument
 put1 :: (BinaryState Integer a)
       => Word8                  -- ^ Opcode
       -> a                      -- ^ First argument
@@ -703,4 +706,17 @@ instance BinaryState Integer Instruction where
         | inRange (153, 158) c -> return $ IF (toEnum $ fromIntegral $ c-153)
         | inRange (159, 164) c -> IF_ICMP (toEnum $ fromIntegral $ c-159) <$> get
         | otherwise -> fail $ "Unknown instruction byte code: " ++ show c
+
+encodeInstructions :: [Instruction] -> B.ByteString
+encodeInstructions code =
+  let p list = forM_ list put
+  in  encodeWith p (0 :: Integer) code
   
+-- | Decode Java method
+decodeMethod :: B.ByteString -> Code
+decodeMethod str = decodeS (0 :: Integer) str
+
+-- | Encode Java method
+encodeMethod :: Code -> B.ByteString
+encodeMethod code = encodeS (0 :: Integer) code
+