{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Capnp.Untyped.Pure
( Slice(..)
, Ptr(..)
, Struct(..)
, List(..)
, ListOf
, length
, sliceIndex
)
where
import Prelude hiding (length)
import Data.Word
import Control.Monad (forM_)
import Data.Default (Default(def))
import Data.Default.Instances.Vector ()
import GHC.Exts (IsList(..))
import GHC.Generics (Generic)
import Capnp.Classes
(Cerialize(..), Decerialize(..), FromStruct(..), Marshal(..), ToPtr(..))
import Internal.Gen.Instances ()
import qualified Capnp.Message as M
import qualified Capnp.Untyped as U
import qualified Data.Vector as V
newtype Slice a = Slice (ListOf a)
deriving(Generic, Show, Ord, Functor, Default, IsList)
data Ptr
= PtrStruct !Struct
| PtrList !List
| PtrCap !M.Client
deriving(Generic, Show, Eq)
data Struct = Struct
{ structData :: Slice Word64
, structPtrs :: Slice (Maybe Ptr)
}
deriving(Generic, Show, Eq)
instance Default Struct
data List
= List0 (ListOf ())
| List1 (ListOf Bool)
| List8 (ListOf Word8)
| List16 (ListOf Word16)
| List32 (ListOf Word32)
| List64 (ListOf Word64)
| ListPtr (ListOf (Maybe Ptr))
| ListStruct (ListOf Struct)
deriving(Generic, Show, Eq)
type ListOf a = V.Vector a
length :: ListOf a -> Int
length = V.length
sliceIndex :: Default a => Int -> Slice a -> a
sliceIndex i (Slice vec)
| i < V.length vec = vec V.! i
| otherwise = def
instance (Default a, Eq a) => Eq (Slice a) where
l@(Slice vl) == r@(Slice vr) = go (max (length vl) (length vr) - 1)
where
go (-1) = True
go 0 = True
go i = sliceIndex i l == sliceIndex i r && go (i-1)
instance Decerialize Struct where
type Cerial msg Struct = U.Struct msg
decerialize struct = Struct
<$> (Slice <$> decerializeWords)
<*> (Slice <$> decerializePtrs)
where
decerializeWords =
let nwords = fromIntegral $ U.structWordCount struct in
V.generateM nwords (`U.getData` struct)
decerializePtrs =
let nptrs = fromIntegral $ U.structPtrCount struct in
V.generateM nptrs (\i -> U.getPtr i struct >>= decerialize)
instance FromStruct M.ConstMsg Struct where
fromStruct = decerialize
instance Marshal Struct where
marshalInto raw (Struct (Slice dataSec) (Slice ptrSec)) = do
forM_ [0..V.length dataSec - 1] $ \i ->
U.setData (dataSec V.! i) i raw
forM_ [0..V.length ptrSec - 1] $ \i -> do
ptr <- cerialize (U.message raw) (ptrSec V.! i)
U.setPtr ptr i raw
instance Cerialize Struct where
cerialize msg struct@(Struct (Slice dataSec) (Slice ptrSec)) = do
raw <- U.allocStruct
msg
(fromIntegral $ V.length dataSec)
(fromIntegral $ V.length ptrSec)
marshalInto raw struct
pure raw
instance Decerialize (Maybe Ptr) where
type Cerial msg (Maybe Ptr) = Maybe (U.Ptr msg)
decerialize Nothing = pure Nothing
decerialize (Just ptr) = Just <$> case ptr of
U.PtrCap cap -> PtrCap <$> U.getClient cap
U.PtrStruct struct -> PtrStruct <$> decerialize struct
U.PtrList list -> PtrList <$> decerialize list
instance Cerialize (Maybe Ptr) where
cerialize _ Nothing = pure Nothing
cerialize msg (Just (PtrStruct struct)) = cerialize msg struct >>= toPtr msg
cerialize msg (Just (PtrList list)) = Just . U.PtrList <$> cerialize msg list
cerialize msg (Just (PtrCap cap)) = Just . U.PtrCap <$> U.appendCap msg cap
decerializeListOf :: (U.ReadCtx m M.ConstMsg, Decerialize a)
=> U.ListOf M.ConstMsg (Cerial M.ConstMsg a) -> m (ListOf a)
decerializeListOf raw = V.generateM (U.length raw) (\i -> U.index i raw >>= decerialize)
decerializeListOfWord :: (U.ReadCtx m M.ConstMsg)
=> U.ListOf M.ConstMsg a -> m (ListOf a)
decerializeListOfWord raw = V.generateM (U.length raw) (`U.index` raw)
instance Decerialize List where
type Cerial msg List = U.List msg
decerialize (U.List0 l) = List0 <$> decerializeListOfWord l
decerialize (U.List1 l) = List1 <$> decerializeListOfWord l
decerialize (U.List8 l) = List8 <$> decerializeListOfWord l
decerialize (U.List16 l) = List16 <$> decerializeListOfWord l
decerialize (U.List32 l) = List32 <$> decerializeListOfWord l
decerialize (U.List64 l) = List64 <$> decerializeListOfWord l
decerialize (U.ListPtr l) = ListPtr <$> decerializeListOf l
decerialize (U.ListStruct l) = ListStruct <$> decerializeListOf l
instance Cerialize List where
cerialize msg (List0 l) = U.List0 <$> U.allocList0 msg (length l)
cerialize msg (List1 l) = U.List1 <$> cerializeListOfWord (U.allocList1 msg) l
cerialize msg (List8 l) = U.List8 <$> cerializeListOfWord (U.allocList8 msg) l
cerialize msg (List16 l) = U.List16 <$> cerializeListOfWord (U.allocList16 msg) l
cerialize msg (List32 l) = U.List32 <$> cerializeListOfWord (U.allocList32 msg) l
cerialize msg (List64 l) = U.List64 <$> cerializeListOfWord (U.allocList64 msg) l
cerialize msg (ListPtr l) = do
raw <- U.allocListPtr msg (length l)
forM_ [0..length l - 1] $ \i -> do
ptr <- cerialize msg (l V.! i)
U.setIndex ptr i raw
pure $ U.ListPtr raw
cerialize msg (ListStruct l) = do
let (maxData, maxPtrs) = measureStructSizes l
raw <- U.allocCompositeList msg maxData maxPtrs (length l)
forM_ [0..length l - 1] $ \i -> do
elt <- U.index i raw
marshalInto elt (l V.! i)
pure $ U.ListStruct raw
where
measureStructSizes :: ListOf Struct -> (Word16, Word16)
measureStructSizes = foldl
(\(!dataSz, !ptrSz) (Struct (Slice dataSec) (Slice ptrSec)) ->
( max dataSz (fromIntegral $ length dataSec)
, max ptrSz (fromIntegral $ length ptrSec)
)
)
(0, 0)
cerializeListOfWord :: U.RWCtx m s => (Int -> m (U.ListOf (M.MutMsg s) a)) -> ListOf a -> m (U.ListOf (M.MutMsg s) a)
cerializeListOfWord alloc list = do
ret <- alloc (length list)
marshalListOfWord ret list
pure ret
marshalListOfWord :: U.RWCtx m s => U.ListOf (M.MutMsg s) a -> ListOf a -> m ()
marshalListOfWord raw l =
forM_ [0..length l - 1] $ \i ->
U.setIndex (l V.! i) i raw