b3762c38cec1e4a9839692ae2f0fdb4603880b5b
[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 Codec.Binary.UTF8.String hiding (encode, decode)
12 import Data.Binary
13 import Data.Binary.Put
14 import qualified Data.ByteString.Lazy as B
15 import Data.Char
16 import Data.String
17 import qualified Data.Map as M
18
19 import JVM.ClassFile
20
21 instance IsString B.ByteString where
22   fromString s = B.pack $ map (fromIntegral . ord) $ encodeString s
23
24 toCharList :: B.ByteString -> [Int]
25 toCharList bstr = map fromIntegral $ B.unpack bstr
26
27 poolSize :: Pool stage -> Int
28 poolSize = M.size
29
30 (!) :: (Ord k) => M.Map k a -> k -> a
31 (!) = (M.!)
32
33 showListIx :: (Show a) => [a] -> String
34 showListIx list = unlines $ zipWith s [1..] list
35   where s i x = show i ++ ":\t" ++ show x
36
37 byteString ::  (Binary t) => t -> B.ByteString
38 byteString x = runPut (put x)
39