Factor Data.BinaryState module out to binary-state package.
authorIlya Portnov <portnov84@rambler.ru>
Sat, 18 Jun 2011 16:57:35 +0000 (22:57 +0600)
committerIlya Portnov <portnov84@rambler.ru>
Sat, 18 Jun 2011 16:57:35 +0000 (22:57 +0600)
.gitignore
Data/BinaryState.hs [deleted file]
Makefile
disassemble.hs [deleted file]
dump-class.hs [new file with mode: 0644]
hs-java.cabal

index d7b78e2472f9f85a8a2001605abd0ac49439e6cf..f64c10b9f6c1d802191d8fd4f91e7e3f20dcb92d 100644 (file)
@@ -4,3 +4,5 @@
 *.bytecode
 *.swp
 .*.swp
+dump-class
+dist/
diff --git a/Data/BinaryState.hs b/Data/BinaryState.hs
deleted file mode 100644 (file)
index fc7fa1d..0000000
+++ /dev/null
@@ -1,97 +0,0 @@
-{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
-module Data.BinaryState where
-
-import Control.Monad
-import qualified Control.Monad.State as State
-import qualified Data.Binary as Binary
-import qualified Data.Binary.Put as Put
-import qualified Data.Binary.Get as Get
-import qualified Data.ByteString.Lazy as B
-import Data.Word
-import Data.Int
-
-type PutState s a = State.StateT s Put.PutM a
-type GetState s a = State.StateT s Binary.Get a
-
-class BinaryState s a where
-  put :: a -> PutState s ()
-  get :: GetState s a
-
-instance (Binary.Binary a) => BinaryState () a where
-  put x = putZ x
-  get = getZ
-
-putZ :: (Binary.Binary a) => a -> PutState s ()
-putZ x = State.lift (Binary.put x)
-
-getZ :: (Binary.Binary a) => GetState s a
-getZ = State.lift Binary.get
-
-------------------------------------------------
-
-encodeS :: (BinaryState s a) => s -> a -> B.ByteString
-encodeS s a = Put.runPut $ State.evalStateT (put a) s
-
-decodeS :: (BinaryState s a) => s -> B.ByteString -> a
-decodeS s str = Get.runGet (State.evalStateT get s) str
-
-decodeWith :: GetState s a -> s -> B.ByteString -> a
-decodeWith getter s str =
-  let (x,_,_) = Get.runGetState (State.evalStateT getter s) str 0
-  in  x
-
-encodeFile :: BinaryState s a => FilePath -> s -> a -> IO ()
-encodeFile f s v = B.writeFile f (encodeS s v)
-
-decodeFile :: BinaryState s a => FilePath -> s -> IO a
-decodeFile f s = liftM (decodeS s) (B.readFile f)
-
-------------------------------------------------
-
-getByte :: GetState s Word8
-getByte = State.lift Binary.getWord8
-
-liftOffset :: (Binary.Binary a) => Integer -> (a -> Binary.Put) -> a -> PutState Integer ()
-liftOffset d fn x = State.modify (+d) >> State.lift (fn x)
-
-putByte :: Word8 -> PutState Integer ()
-putByte x = liftOffset 1 Put.putWord8 x
-
-isEmpty :: GetState s Bool
-isEmpty = State.lift Get.isEmpty
-
-skip :: Int -> GetState s ()
-skip n = State.lift (Get.skip n)
-
-getOffset :: PutState Integer Integer
-getOffset = State.get
-
-bytesRead :: GetState s Int64
-bytesRead = State.lift Get.bytesRead
-
---------------------------------------------------
-
-instance BinaryState Integer Word8 where
-  put x = putByte x
-  get = getZ
-
-instance BinaryState Integer Word16 where
-  put x = liftOffset 2 Binary.put x
-  get = getZ
-
-instance BinaryState Integer Word32 where
-  put x = liftOffset 4 Binary.put x
-  get = getZ
-
-instance (BinaryState s a, BinaryState s b) => BinaryState s (a,b) where
-  put (x,y) = put x >> put y
-  get = do
-    x <- get
-    y <- get
-    return (x,y)
-
---------------------------------------------------
-
--- instance (Binary.Binary a, Storable a) => BinaryState Integer a where
---   put x = liftOffset (fromIntegral $ sizeOf x) Binary.put x
---   get = getZ
index 815c13d2fc146cc30445d806c738f0bb32e8cdc6..84775139813292e81e65bf4c2d6fec29dd1b3273 100644 (file)
--- a/Makefile
+++ b/Makefile
@@ -1,8 +1,8 @@
 GHC=ghc --make -fwarn-unused-imports
 
-all: disassemble
+all: dump-class
 
-disassemble: disassemble.hs */*.hs
+dump-class: dump-class.hs */*.hs
        $(GHC) $<
 
 clean:
diff --git a/disassemble.hs b/disassemble.hs
deleted file mode 100644 (file)
index bb6512f..0000000
+++ /dev/null
@@ -1,37 +0,0 @@
-{-# LANGUAGE OverloadedStrings #-}
-module Main where
-
-import Control.Monad
-import Data.Array
-import System.Environment
-import qualified Data.ByteString.Lazy as B
-import Text.Printf
-
-import Data.BinaryState
-import JVM.Types
-import JVM.Converter
-import JVM.Assembler
-
-main = do
-  args <- getArgs
-  case args of
-    [clspath] -> do
-      cls <- decompileFile clspath
-      putStr "Class: "
-      B.putStrLn (this cls)
-      putStrLn "Constants pool:"
-      forM_ (assocs $ constantPool cls) $ \(i, c) ->
-        putStrLn $ printf "  #%d:\t%s" i (show c)
-      putStrLn "Methods:"
-      forM_ (methods cls) $ \m -> do
-        putStr ">> Method "
-        B.putStr (methodName m)
-        print (methodSignature m)
-        case attrByName m "Code" of
-          Nothing -> putStrLn "(no code)\n"
-          Just bytecode -> let code = decodeS (0 :: Integer) bytecode
-                           in  forM_ (codeInstructions code) $ \i -> do
-                                 putStr "  "
-                                 print i
-
-    _ -> error "Synopsis: disassemble File.class"
diff --git a/dump-class.hs b/dump-class.hs
new file mode 100644 (file)
index 0000000..bb6512f
--- /dev/null
@@ -0,0 +1,37 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Main where
+
+import Control.Monad
+import Data.Array
+import System.Environment
+import qualified Data.ByteString.Lazy as B
+import Text.Printf
+
+import Data.BinaryState
+import JVM.Types
+import JVM.Converter
+import JVM.Assembler
+
+main = do
+  args <- getArgs
+  case args of
+    [clspath] -> do
+      cls <- decompileFile clspath
+      putStr "Class: "
+      B.putStrLn (this cls)
+      putStrLn "Constants pool:"
+      forM_ (assocs $ constantPool cls) $ \(i, c) ->
+        putStrLn $ printf "  #%d:\t%s" i (show c)
+      putStrLn "Methods:"
+      forM_ (methods cls) $ \m -> do
+        putStr ">> Method "
+        B.putStr (methodName m)
+        print (methodSignature m)
+        case attrByName m "Code" of
+          Nothing -> putStrLn "(no code)\n"
+          Just bytecode -> let code = decodeS (0 :: Integer) bytecode
+                           in  forM_ (codeInstructions code) $ \i -> do
+                                 putStr "  "
+                                 print i
+
+    _ -> error "Synopsis: disassemble File.class"
index 266f99f8a61c07d9b86041c07cebcbca0e47ae11..eb460385c91c5ff32c0a0f4257e64cb9e56ec1e5 100644 (file)
@@ -11,18 +11,17 @@ Build-Type:     Simple
 Description:    This package declares data types for Java .class files format and functions
                 to assemble/disassemble Java bytecode.
 
-Extra-source-files: disassemble.hs
+Extra-source-files: dump-class.hs
 
 library
-  Exposed-Modules: Data.BinaryState
-                   JVM.Types
+  Exposed-Modules: JVM.Types
                    JVM.ClassFile
                    JVM.Assembler
                    JVM.Converter
 
   Build-Depends:  base >= 3 && <= 5, haskell98, containers, binary,
                   mtl, directory, filepath, utf8-string, array,
-                  bytestring, data-binary-ieee754
+                  bytestring, data-binary-ieee754, binary-state
 
   ghc-options: -fwarn-unused-imports