{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Capnp.Classes
( IsWord(..)
, ListElem(..)
, MutListElem(..)
, IsPtr(..)
, FromStruct(..)
, ToStruct(..)
, Allocate(..)
, Marshal(..)
, Cerialize(..)
, Decerialize(..)
) where
import Data.Bits
import Data.Int
import Data.ReinterpretCast
import Data.Word
import Control.Monad.Catch (MonadThrow(throwM))
import Data.Capnp.Bits (Word1(..))
import Data.Capnp.Errors (Error(SchemaViolationError))
import Data.Capnp.Untyped (ListOf, Ptr(..), ReadCtx, Struct, messageDefault)
import qualified Data.Capnp.Message as M
import qualified Data.Capnp.Untyped as U
class IsWord a where
fromWord :: Word64 -> a
toWord :: a -> Word64
class ListElem msg e where
data List msg e
length :: List msg e -> Int
index :: U.ReadCtx m msg => Int -> List msg e -> m e
class (ListElem (M.MutMsg s) e) => MutListElem s e where
setIndex :: U.RWCtx m s => e -> Int -> List (M.MutMsg s) e -> m ()
newList :: M.WriteCtx m s => M.MutMsg s -> Int -> m (List (M.MutMsg s) e)
class Allocate s e where
new :: M.WriteCtx m s => M.MutMsg s -> m e
class Decerialize a where
type Cerial msg a
decerialize :: U.ReadCtx m M.ConstMsg => Cerial M.ConstMsg a -> m a
class Decerialize a => Marshal a where
marshalInto :: U.RWCtx m s => Cerial (M.MutMsg s) a -> a -> m ()
class Decerialize a => Cerialize s a where
cerialize :: U.RWCtx m s => M.MutMsg s -> a -> m (Cerial (M.MutMsg s) a)
default cerialize :: (U.RWCtx m s, Marshal a, Allocate s (Cerial (M.MutMsg s) a))
=> M.MutMsg s -> a -> m (Cerial (M.MutMsg s) a)
cerialize msg value = do
raw <- new msg
marshalInto raw value
pure raw
class IsPtr msg a where
fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m a
toPtr :: a -> Maybe (Ptr msg)
class FromStruct msg a where
fromStruct :: ReadCtx m msg => Struct msg -> m a
class ToStruct msg a where
toStruct :: a -> Struct msg
instance IsWord Bool where
fromWord n = (n .&. 1) == 1
toWord True = 1
toWord False = 0
instance IsWord Word1 where
fromWord = Word1 . fromWord
toWord = toWord . word1ToBool
instance IsWord Int8 where
fromWord = fromIntegral
toWord = fromIntegral
instance IsWord Int16 where
fromWord = fromIntegral
toWord = fromIntegral
instance IsWord Int32 where
fromWord = fromIntegral
toWord = fromIntegral
instance IsWord Int64 where
fromWord = fromIntegral
toWord = fromIntegral
instance IsWord Word8 where
fromWord = fromIntegral
toWord = fromIntegral
instance IsWord Word16 where
fromWord = fromIntegral
toWord = fromIntegral
instance IsWord Word32 where
fromWord = fromIntegral
toWord = fromIntegral
instance IsWord Word64 where
fromWord = fromIntegral
toWord = fromIntegral
instance IsWord Float where
fromWord = wordToFloat . fromIntegral
toWord = fromIntegral . floatToWord
instance IsWord Double where
fromWord = wordToDouble
toWord = doubleToWord
expected :: MonadThrow m => String -> m a
expected msg = throwM $ SchemaViolationError $ "expected " ++ msg
instance IsPtr msg (ListOf msg ()) where
fromPtr msg Nothing = pure $ messageDefault msg
fromPtr msg (Just (PtrList (U.List0 list))) = pure list
fromPtr _ _ = expected "pointer to list with element size 0"
toPtr = Just . PtrList . U.List0
instance IsPtr msg (ListOf msg Word8) where
fromPtr msg Nothing = pure $ messageDefault msg
fromPtr msg (Just (PtrList (U.List8 list))) = pure list
fromPtr _ _ = expected "pointer to list with element size 8"
toPtr = Just . PtrList . U.List8
instance IsPtr msg (ListOf msg Word16) where
fromPtr msg Nothing = pure $ messageDefault msg
fromPtr msg (Just (PtrList (U.List16 list))) = pure list
fromPtr _ _ = expected "pointer to list with element size 16"
toPtr = Just . PtrList . U.List16
instance IsPtr msg (ListOf msg Word32) where
fromPtr msg Nothing = pure $ messageDefault msg
fromPtr msg (Just (PtrList (U.List32 list))) = pure list
fromPtr _ _ = expected "pointer to list with element size 32"
toPtr = Just . PtrList . U.List32
instance IsPtr msg (ListOf msg Word64) where
fromPtr msg Nothing = pure $ messageDefault msg
fromPtr msg (Just (PtrList (U.List64 list))) = pure list
fromPtr _ _ = expected "pointer to list with element size 64"
toPtr = Just . PtrList . U.List64
instance IsPtr msg (ListOf msg Bool) where
fromPtr msg Nothing = pure $ messageDefault msg
fromPtr msg (Just (PtrList (U.List1 list))) = pure list
fromPtr _ _ = expected "pointer to list with element size 1."
toPtr = Just . PtrList . U.List1
instance IsPtr msg (Maybe (Ptr msg)) where
fromPtr _ = pure
toPtr = id
instance IsPtr msg (ListOf msg (Struct msg)) where
fromPtr msg Nothing = pure $ messageDefault msg
fromPtr msg (Just (PtrList (U.ListStruct list))) = pure list
fromPtr _ _ = expected "pointer to list of structs"
toPtr = Just . PtrList . U.ListStruct
instance FromStruct msg (Struct msg) where
fromStruct = pure
instance ToStruct msg (Struct msg) where
toStruct = id
instance IsPtr msg (Struct msg) where
fromPtr msg Nothing = fromStruct (go msg) where
go :: msg -> Struct msg
go = messageDefault
fromPtr msg (Just (PtrStruct s)) = fromStruct s
fromPtr _ _ = expected "pointer to struct"
toPtr = Just . PtrStruct