{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Capnp.Basics
( Text
, Data(..)
, ListElem(..)
, MutListElem(..)
, getData
, getText
, newData
, newText
, dataBytes
, textBuffer
, textBytes
) where
import Data.Word
import Control.Monad (when, (>=>))
import Control.Monad.Catch (MonadThrow(throwM))
import qualified Data.ByteString as BS
import Capnp.Classes
(FromPtr(..), ListElem(..), MutListElem(..), ToPtr(..))
import Internal.Gen.Instances ()
import qualified Capnp.Errors as E
import qualified Capnp.Message as M
import qualified Capnp.Untyped as U
newtype Text msg = Text (U.ListOf msg Word8)
newtype Data msg = Data (U.ListOf msg Word8)
newData :: M.WriteCtx m s => M.MutMsg s -> Int -> m (Data (M.MutMsg s))
newData msg len = Data <$> U.allocList8 msg len
getData :: U.ReadCtx m msg => U.ListOf msg Word8 -> m (Data msg)
getData = pure . Data
newText :: M.WriteCtx m s => M.MutMsg s -> Int -> m (Text (M.MutMsg s))
newText msg len =
Text <$> U.allocList8 msg (len+1)
getText :: U.ReadCtx m msg => U.ListOf msg Word8 -> m (Text msg)
getText list = do
let len = U.length list
when (len == 0) $ throwM $ E.SchemaViolationError
"Text is not NUL-terminated (list of bytes has length 0)"
lastByte <- U.index (len - 1) list
when (lastByte /= 0) $ throwM $ E.SchemaViolationError $
"Text is not NUL-terminated (last byte is " ++ show lastByte ++ ")"
pure $ Text list
dataBytes :: U.ReadCtx m msg => Data msg -> m BS.ByteString
dataBytes (Data list) = U.rawBytes list
textBuffer :: U.ReadCtx m msg => Text msg -> m (U.ListOf msg Word8)
textBuffer (Text list) = U.take (U.length list - 1) list
textBytes :: U.ReadCtx m msg => Text msg -> m BS.ByteString
textBytes = textBuffer >=> U.rawBytes
instance ListElem msg (Data msg) where
newtype List msg (Data msg) = DataList (U.ListOf msg (Maybe (U.Ptr msg)))
listFromPtr msg ptr = DataList <$> fromPtr msg ptr
toUntypedList (DataList l) = U.ListPtr l
length (DataList l) = U.length l
index i (DataList l) = ptrListIndex i l
instance MutListElem s (Data (M.MutMsg s)) where
setIndex (Data e) i (DataList l) =
U.setIndex (Just (U.PtrList (U.List8 e))) i l
newList msg len = DataList <$> U.allocListPtr msg len
instance ListElem msg (Text msg) where
newtype List msg (Text msg) = TextList (U.ListOf msg (Maybe (U.Ptr msg)))
listFromPtr msg ptr = TextList <$> fromPtr msg ptr
toUntypedList (TextList l) = U.ListPtr l
length (TextList l) = U.length l
index i (TextList l) = ptrListIndex i l
instance MutListElem s (Text (M.MutMsg s)) where
setIndex (Text e) i (TextList l) =
U.setIndex (Just (U.PtrList (U.List8 e))) i l
newList msg len = TextList <$> U.allocListPtr msg len
ptrListIndex :: (U.ReadCtx m msg, FromPtr msg a) => Int -> U.ListOf msg (Maybe (U.Ptr msg)) -> m a
ptrListIndex i list = do
ptr <- U.index i list
fromPtr (U.message list) ptr
instance FromPtr msg (Data msg) where
fromPtr msg ptr = fromPtr msg ptr >>= getData
instance ToPtr s (Data (M.MutMsg s)) where
toPtr msg (Data l) = toPtr msg l
instance FromPtr msg (Text msg) where
fromPtr msg ptr = case ptr of
Just _ ->
fromPtr msg ptr >>= getText
Nothing -> do
Data bytes <- fromPtr msg ptr
pure $ Text bytes
instance ToPtr s (Text (M.MutMsg s)) where
toPtr msg (Text l) = toPtr msg l