cabal: bump data-default dependency to 0.5.0.
[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   mapFindIndex,
9   byteString
10   ) where
11
12 import Data.Binary
13 import Data.Binary.Put
14 import qualified Data.ByteString.Lazy as B
15 import qualified Data.Map as M
16 import Data.Default
17 import Data.List
18
19 import JVM.ClassFile
20
21 instance Default B.ByteString where
22   def = B.empty
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 i, Show a) => [(i,a)] -> String
34 showListIx list = unlines $ map s 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
40 mapFindIndex :: (Num k) => (v -> Bool) -> M.Map k v -> Maybe k
41 mapFindIndex check m =
42   case find (check . snd) (M.assocs m) of
43     Nothing -> Nothing
44     Just (k,_) -> Just k
45