module Binary.Neko.Globals where
import Data.ByteString.Lazy as BS
import Data.ByteString.Lazy.Char8 as BSChar
import Data.Binary.Get
import Data.Binary.Put
import Data.Either
import Data.Maybe
import Data.Word
import Data.Int
data Global =
GlobalVar String
| GlobalFunction (Int, Int)
| GlobalString String
| GlobalFloat String
| GlobalDebug ([String], [(Int, Int)])
| GlobalVersion Int
deriving (Show, Eq)
readGlobals :: Word32
-> ByteString
-> Maybe ([Global], ByteString)
readGlobals n bs = if (isRight res) then (Just (gs, rest)) else Nothing
where res = runGetOrFail (getGlobals n) bs
Right (rest, _, gs) = res
readGlobal :: ByteString
-> Maybe (Global, ByteString)
readGlobal bs = if (isRight res) then (Just (g, rest)) else Nothing
where res = runGetOrFail getGlobal bs
Right (rest, _, g) = res
getGlobals :: Word32
-> Get [Global]
getGlobals 0 = return []
getGlobals n = getGlobal >>= \g -> getGlobals (n 1) >>= \gs -> return (g:gs)
getGlobal :: Get Global
getGlobal = getWord8
>>= \b -> if (b == 1) then getGlobalVar else
if (b == 2) then error "TODO getGlobal: implement GlobalFunction" else
if (b == 3) then getGlobalString else
if (b == 4) then error "TODO getGlobal: implement GlobalFloat" else
if (b == 5) then error "TODO getGlobal: implement GlobalDebug" else
if (b == 6) then error "TODO getGlobal: implement GlobalVersion" else
fail "getGlobal: urecognized global"
getGlobalVar :: Get Global
getGlobalVar = getLazyByteStringNul >>= \b -> return ( GlobalVar $ BSChar.unpack b)
getGlobalString :: Get Global
getGlobalString = getWord16le
>>= \length -> getLazyByteString (fromIntegral length)
>>= \s -> return (GlobalString $ BSChar.unpack s)
putGlobal :: Global -> Put
putGlobal (GlobalVar s) = putWord8 1 >> putLazyByteString (BSChar.pack s) >> putWord8 0
putGlobal (GlobalString s) = putWord8 3
>> putWord16le (fromIntegral $ Prelude.length s) >> putLazyByteString (BSChar.pack s)
putGlobal g = error ("Unimplemented: " ++ (show g))
putGlobals :: [Global] -> Put
putGlobals [] = return ()
putGlobals (g:gs) = putGlobal g >> putGlobals gs