Cleanup, minor updates.
[hs-java.git] / JVM / Common.hs
1 {-# LANGUAGE TypeFamilies, StandaloneDeriving, FlexibleInstances, FlexibleContexts, UndecidableInstances #-}
2 -- | This module declares some commonly used functions and instances.
3 module JVM.Common
4   (toCharList,
5   poolSize,
6   (!),
7   showListIx,
8   byteString
9   ) where
10
11 import Data.Binary
12 import Data.Binary.Put
13 import qualified Data.ByteString.Lazy as B
14 import qualified Data.Map as M
15 import Data.Default
16
17 import JVM.ClassFile
18
19 instance Default B.ByteString where
20   def = B.empty
21
22 instance Default Word16 where
23   def = 0
24
25 toCharList :: B.ByteString -> [Int]
26 toCharList bstr = map fromIntegral $ B.unpack bstr
27
28 poolSize :: Pool stage -> Int
29 poolSize = M.size
30
31 (!) :: (Ord k) => M.Map k a -> k -> a
32 (!) = (M.!)
33
34 showListIx :: (Show a) => [a] -> String
35 showListIx list = unlines $ zipWith s [1..] list
36   where s i x = show i ++ ":\t" ++ show x
37
38 byteString ::  (Binary t) => t -> B.ByteString
39 byteString x = runPut (put x)
40