{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Language.JVM.Utils
(
SizedList (..)
, listSize
, SizedByteString (..)
, byteStringSize
, SizedList16
, SizedByteString32
, SizedByteString16
, sizedByteStringFromText
, sizedByteStringToText
, tryDecode
, BitSet (..)
, Enumish(..)
, BitSet16
, trd
) where
import Data.Binary
import Data.Binary.Get
import Data.Binary.Put
import Data.Bits
import Data.List as List
import Data.Set as Set
import Data.String
import Control.DeepSeq (NFData)
import Control.Monad
import qualified Data.Text as Text
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Encoding.Error as TE
import qualified Data.ByteString as BS
newtype SizedList w a = SizedList
{ unSizedList :: [ a ]
} deriving (Show, Eq, Functor, NFData, Ord)
listSize :: Num w => SizedList w a -> w
listSize =
fromIntegral . length . unSizedList
instance Foldable (SizedList w) where
foldMap am =
foldMap am . unSizedList
instance Traversable (SizedList w) where
traverse afb ta =
SizedList <$> traverse afb (unSizedList ta)
instance (Binary w, Integral w, Binary a) => Binary (SizedList w a) where
get = do
len <- get :: Get w
SizedList <$> replicateM (fromIntegral len) get
put sl@(SizedList l) = do
put (listSize sl)
forM_ l put
newtype SizedByteString w = SizedByteString
{ unSizedByteString :: BS.ByteString
} deriving (Show, Eq, NFData, Ord, IsString)
byteStringSize :: (Num w) => SizedByteString w -> w
byteStringSize =
fromIntegral . BS.length . unSizedByteString
instance (Binary w, Integral w) => Binary (SizedByteString w) where
get = do
x <- get :: Get w
SizedByteString <$> getByteString (fromIntegral x)
put sbs@(SizedByteString bs) = do
put (byteStringSize sbs)
putByteString bs
replaceJavaZeroWithNormalZero :: BS.ByteString -> BS.ByteString
replaceJavaZeroWithNormalZero = go
where
go bs =
case BS.breakSubstring "\192\128" bs of
(h, "") -> h
(h, t) -> h `BS.append` "\0" `BS.append` go (BS.drop 2 t)
replaceNormalZeroWithJavaZero::BS.ByteString -> BS.ByteString
replaceNormalZeroWithJavaZero = go
where
go bs =
case BS.breakSubstring "\0" bs of
(h, "") -> h
(h, t) -> h `BS.append` "\192\128" `BS.append` go (BS.drop 1 t)
sizedByteStringToText ::
SizedByteString w
-> Either TE.UnicodeException Text.Text
sizedByteStringToText (SizedByteString bs) =
let rst = TE.decodeUtf8' bs
in case rst of
Right txt -> Right txt
Left _ -> tryDecode bs
tryDecode :: BS.ByteString -> Either TE.UnicodeException Text.Text
tryDecode = TE.decodeUtf8' . replaceJavaZeroWithNormalZero
sizedByteStringFromText ::
Text.Text
-> SizedByteString w
sizedByteStringFromText t
= SizedByteString . replaceNormalZeroWithJavaZero . TE.encodeUtf8 $ t
class (Eq a, Ord a) => Enumish a where
inOrder :: [(Int, a)]
fromEnumish :: a -> Int
fromEnumish a = let Just (i, _) = List.find ((== a) . snd) $ inOrder in i
toEnumish :: Int -> Maybe a
toEnumish i = snd <$> (List.find ((== i) . fst) $ inOrder)
newtype BitSet w a = BitSet
{ toSet :: Set.Set a
} deriving (Ord, Show, Eq, NFData)
bitSetToWord :: (Enumish a, Bits w) => BitSet w a -> w
bitSetToWord =
toWord . Set.toList . toSet
toWord :: (Enumish a, Bits w) => [a] -> w
toWord =
List.foldl' (\a -> setBit a . fromEnumish) zeroBits
instance (Show w, Bits w, Binary w, Enumish a) => Binary (BitSet w a) where
get = do
word <- get :: Get w
return . BitSet $ Set.fromList [ x | (i, x) <- inOrder, testBit word i ]
put = put . bitSetToWord
type SizedList16 = SizedList Word16
type SizedByteString32 = SizedByteString Word32
type SizedByteString16 = SizedByteString Word16
type BitSet16 = BitSet Word16
trd :: (a, b, c) -> c
trd (_, _, c) = c