c2ab55d89cc119c02d672421fdd7e656d76d82cd
[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 Foreign.Storable
11 import Data.Word
12 import Data.Int
13
14 type PutState s a = State.StateT s Put.PutM a
15 type GetState s a = State.StateT s Binary.Get a
16
17 class BinaryState s a where
18   put :: a -> PutState s ()
19   get :: GetState s a
20
21 instance (Binary.Binary a) => BinaryState () a where
22   put x = putZ x
23   get = getZ
24
25 putZ :: (Binary.Binary a) => a -> PutState s ()
26 putZ x = State.lift (Binary.put x)
27
28 getZ :: (Binary.Binary a) => GetState s a
29 getZ = State.lift Binary.get
30
31 ------------------------------------------------
32
33 encodeS :: (BinaryState s a) => s -> a -> B.ByteString
34 encodeS s a = Put.runPut $ State.evalStateT (put a) s
35
36 decodeS :: (BinaryState s a) => s -> B.ByteString -> a
37 decodeS s str = Get.runGet (State.evalStateT get s) str
38
39 encodeFile :: BinaryState s a => FilePath -> s -> a -> IO ()
40 encodeFile f s v = B.writeFile f (encodeS s v)
41
42 decodeFile :: BinaryState s a => FilePath -> s -> IO a
43 decodeFile f s = liftM (decodeS s) (B.readFile f)
44
45 ------------------------------------------------
46
47 getByte :: GetState s Word8
48 getByte = State.lift Binary.getWord8
49
50 liftOffset :: (Binary.Binary a) => Integer -> (a -> Binary.Put) -> a -> PutState Integer ()
51 liftOffset d fn x = State.modify (+d) >> State.lift (fn x)
52
53 putByte :: Word8 -> PutState Integer ()
54 putByte x = liftOffset 1 Put.putWord8 x
55
56 isEmpty :: GetState s Bool
57 isEmpty = State.lift Get.isEmpty
58
59 skip :: Int -> GetState s ()
60 skip n = State.lift (Get.skip n)
61
62 getOffset :: PutState Integer Integer
63 getOffset = State.get
64
65 bytesRead :: GetState s Int64
66 bytesRead = State.lift Get.bytesRead
67
68 --------------------------------------------------
69
70 instance BinaryState Integer Word8 where
71   put x = putByte x
72   get = getZ
73
74 instance BinaryState Integer Word16 where
75   put x = liftOffset 2 Binary.put x
76   get = getZ
77
78 instance BinaryState Integer Word32 where
79   put x = liftOffset 4 Binary.put x
80   get = getZ
81
82 instance (BinaryState s a, BinaryState s b) => BinaryState s (a,b) where
83   put (x,y) = put x >> put y
84   get = do
85     x <- get
86     y <- get
87     return (x,y)
88
89 --------------------------------------------------
90
91 -- instance (Binary.Binary a, Storable a) => BinaryState Integer a where
92 --   put x = liftOffset (fromIntegral $ sizeOf x) Binary.put x
93 --   get = getZ