{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
module Capnp.GenHelpers where
import Data.Bits
import Data.Word
import Data.Maybe (fromJust)
import qualified Data.ByteString as BS
import Capnp.Bits
import Capnp (bsToMsg, evalLimitT)
import qualified Capnp.Classes as C
import qualified Capnp.Message as M
import qualified Capnp.Untyped as U
getWordField :: (U.ReadCtx m msg, C.IsWord a) => U.Struct msg -> Int -> Int -> Word64 -> m a
getWordField struct idx offset def = fmap
( C.fromWord
. xor def
. (`shiftR` offset)
)
(U.getData idx struct)
setWordField ::
( U.RWCtx m s
, Bounded a, Integral a, C.IsWord a, Bits a
)
=> U.Struct (M.MutMsg s) -> a -> Int -> Int -> Word64 -> m ()
setWordField struct value idx offset def = do
old <- U.getData idx struct
let new = replaceBits (value `xor` C.fromWord def) old offset
U.setData new idx struct
embedCapPtr :: M.WriteCtx m s => M.MutMsg s -> M.Client -> m (Maybe (U.Ptr (M.MutMsg s)))
embedCapPtr msg client =
Just . U.PtrCap <$> U.appendCap msg client
getPtrConst :: C.FromPtr M.ConstMsg a => BS.ByteString -> a
getPtrConst bytes = fromJust $ do
msg <- bsToMsg bytes
evalLimitT maxBound $ U.rootPtr msg >>= U.getPtr 0 >>= C.fromPtr msg
getTag :: U.ReadCtx m msg => U.Struct msg -> Int -> m Word16
getTag struct offset = do
word <- U.getData (offset `div` 4) struct
pure $ fromIntegral $ word `shiftR` ((offset `mod` 4) * 16)