Cleanup: remove unused imports.
[hs-java.git] / Data / BinaryState.hs
1 {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
2 module Data.BinaryState where
3
4 import Control.Monad
5 import qualified Control.Monad.State as State
6 import qualified Data.Binary as Binary
7 import qualified Data.Binary.Put as Put
8 import qualified Data.Binary.Get as Get
9 import qualified Data.ByteString.Lazy as B
10 import Data.Word
11 import Data.Int
12
13 type PutState s a = State.StateT s Put.PutM a
14 type GetState s a = State.StateT s Binary.Get a
15
16 class BinaryState s a where
17   put :: a -> PutState s ()
18   get :: GetState s a
19
20 instance (Binary.Binary a) => BinaryState () a where
21   put x = putZ x
22   get = getZ
23
24 putZ :: (Binary.Binary a) => a -> PutState s ()
25 putZ x = State.lift (Binary.put x)
26
27 getZ :: (Binary.Binary a) => GetState s a
28 getZ = State.lift Binary.get
29
30 ------------------------------------------------
31
32 encodeS :: (BinaryState s a) => s -> a -> B.ByteString
33 encodeS s a = Put.runPut $ State.evalStateT (put a) s
34
35 decodeS :: (BinaryState s a) => s -> B.ByteString -> a
36 decodeS s str = Get.runGet (State.evalStateT get s) str
37
38 decodeWith :: GetState s a -> s -> B.ByteString -> a
39 decodeWith getter s str =
40   let (x,_,_) = Get.runGetState (State.evalStateT getter s) str 0
41   in  x
42
43 encodeFile :: BinaryState s a => FilePath -> s -> a -> IO ()
44 encodeFile f s v = B.writeFile f (encodeS s v)
45
46 decodeFile :: BinaryState s a => FilePath -> s -> IO a
47 decodeFile f s = liftM (decodeS s) (B.readFile f)
48
49 ------------------------------------------------
50
51 getByte :: GetState s Word8
52 getByte = State.lift Binary.getWord8
53
54 liftOffset :: (Binary.Binary a) => Integer -> (a -> Binary.Put) -> a -> PutState Integer ()
55 liftOffset d fn x = State.modify (+d) >> State.lift (fn x)
56
57 putByte :: Word8 -> PutState Integer ()
58 putByte x = liftOffset 1 Put.putWord8 x
59
60 isEmpty :: GetState s Bool
61 isEmpty = State.lift Get.isEmpty
62
63 skip :: Int -> GetState s ()
64 skip n = State.lift (Get.skip n)
65
66 getOffset :: PutState Integer Integer
67 getOffset = State.get
68
69 bytesRead :: GetState s Int64
70 bytesRead = State.lift Get.bytesRead
71
72 --------------------------------------------------
73
74 instance BinaryState Integer Word8 where
75   put x = putByte x
76   get = getZ
77
78 instance BinaryState Integer Word16 where
79   put x = liftOffset 2 Binary.put x
80   get = getZ
81
82 instance BinaryState Integer Word32 where
83   put x = liftOffset 4 Binary.put x
84   get = getZ
85
86 instance (BinaryState s a, BinaryState s b) => BinaryState s (a,b) where
87   put (x,y) = put x >> put y
88   get = do
89     x <- get
90     y <- get
91     return (x,y)
92
93 --------------------------------------------------
94
95 -- instance (Binary.Binary a, Storable a) => BinaryState Integer a where
96 --   put x = liftOffset (fromIntegral $ sizeOf x) Binary.put x
97 --   get = getZ