capnp-0.3.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Capnp.Untyped

Description

The types and functions in this module know about things like structs and lists, but are not schema aware.

Each of the data types exported by this module is parametrized over a Message type (see Data.Capnp.Message), used as the underlying storage.

Synopsis

Documentation

data Ptr msg Source #

A an absolute pointer to a value (of arbitrary type) in a message. Note that there is no variant for far pointers, which don't make sense with absolute addressing.

Constructors

PtrCap msg !Word32 
PtrList (List msg) 
PtrStruct (Struct msg) 
Instances
IsPtr msg (Maybe (Ptr msg)) Source #

IsPtr instance for pointers -- this is just the identity.

Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Maybe (Ptr msg)) Source #

toPtr :: Maybe (Ptr msg) -> Maybe (Ptr msg) Source #

Thaw msg => Thaw (Ptr msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (Ptr msg) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Ptr msg -> m (Mutable s (Ptr msg)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Ptr msg) -> m (Ptr msg) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Ptr msg -> m (Mutable s (Ptr msg)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Ptr msg) -> m (Ptr msg) Source #

HasMessage (Ptr msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type InMessage (Ptr msg) :: * Source #

Methods

message :: Ptr msg -> InMessage (Ptr msg) Source #

Thaw msg => Thaw (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg (Maybe (Ptr msg))) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Maybe (Ptr msg)) -> m (Mutable s (ListOf msg (Maybe (Ptr msg)))) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Maybe (Ptr msg)) -> m (Mutable s (ListOf msg (Maybe (Ptr msg)))) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source #

MessageDefault (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (ListOf msg (Maybe (Ptr msg))) -> ListOf msg (Maybe (Ptr msg)) Source #

type Mutable s (Ptr msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (Ptr msg) = Ptr (Mutable s msg)
type Mutable s (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg (Maybe (Ptr msg))) = ListOf (Mutable s msg) (Maybe (Ptr (Mutable s msg)))
type InMessage (Ptr msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type InMessage (Ptr msg) = msg

data List msg Source #

A list of values (of arbitrary type) in a message.

Constructors

List0 (ListOf msg ()) 
List1 (ListOf msg Bool) 
List8 (ListOf msg Word8) 
List16 (ListOf msg Word16) 
List32 (ListOf msg Word32) 
List64 (ListOf msg Word64) 
ListPtr (ListOf msg (Maybe (Ptr msg))) 
ListStruct (ListOf msg (Struct msg)) 
Instances
Thaw msg => Thaw (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (List msg) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => List msg -> m (Mutable s (List msg)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List msg) -> m (List msg) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => List msg -> m (Mutable s (List msg)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List msg) -> m (List msg) Source #

HasMessage (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type InMessage (List msg) :: * Source #

Methods

message :: List msg -> InMessage (List msg) Source #

type Mutable s (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (List msg) = List (Mutable s msg)
type InMessage (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type InMessage (List msg) = msg

data Struct msg Source #

A struct value in a message.

Instances
ToStruct msg (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

toStruct :: Struct msg -> Struct msg Source #

FromStruct msg (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Struct msg) Source #

IsPtr msg (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Struct msg) Source #

toPtr :: Struct msg -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (ListOf msg (Struct msg)) Source #

toPtr :: ListOf msg (Struct msg) -> Maybe (Ptr msg) Source #

Thaw msg => Thaw (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (Struct msg) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Struct msg -> m (Mutable s (Struct msg)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Struct msg) -> m (Struct msg) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Struct msg -> m (Mutable s (Struct msg)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Struct msg) -> m (Struct msg) Source #

MessageDefault (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (Struct msg) -> Struct msg Source #

HasMessage (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type InMessage (Struct msg) :: * Source #

Methods

message :: Struct msg -> InMessage (Struct msg) Source #

Thaw msg => Thaw (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg (Struct msg)) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Struct msg) -> m (Mutable s (ListOf msg (Struct msg))) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Struct msg) -> m (Mutable s (ListOf msg (Struct msg))) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source #

MessageDefault (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (ListOf msg (Struct msg)) -> ListOf msg (Struct msg) Source #

type Mutable s (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (Struct msg) = Struct (Mutable s msg)
type Mutable s (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg (Struct msg)) = ListOf (Mutable s msg) (Struct (Mutable s msg))
type InMessage (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type InMessage (Struct msg) = msg

data ListOf msg a Source #

A list of values of type a in a message.

Instances
IsPtr msg (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (ListOf msg (Struct msg)) Source #

toPtr :: ListOf msg (Struct msg) -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Bool) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (ListOf msg Bool) Source #

toPtr :: ListOf msg Bool -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Word64) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (ListOf msg Word64) Source #

toPtr :: ListOf msg Word64 -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Word32) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (ListOf msg Word32) Source #

toPtr :: ListOf msg Word32 -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Word16) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (ListOf msg Word16) Source #

toPtr :: ListOf msg Word16 -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Word8) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (ListOf msg Word8) Source #

toPtr :: ListOf msg Word8 -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (ListOf msg ()) Source #

toPtr :: ListOf msg () -> Maybe (Ptr msg) Source #

Thaw msg => Thaw (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg (Maybe (Ptr msg))) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Maybe (Ptr msg)) -> m (Mutable s (ListOf msg (Maybe (Ptr msg)))) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Maybe (Ptr msg)) -> m (Mutable s (ListOf msg (Maybe (Ptr msg)))) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source #

Thaw msg => Thaw (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg (Struct msg)) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Struct msg) -> m (Mutable s (ListOf msg (Struct msg))) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg (Struct msg) -> m (Mutable s (ListOf msg (Struct msg))) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source #

Thaw msg => Thaw (ListOf msg Word64) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Word64) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word64 -> m (Mutable s (ListOf msg Word64)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word64) -> m (ListOf msg Word64) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word64 -> m (Mutable s (ListOf msg Word64)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word64) -> m (ListOf msg Word64) Source #

Thaw msg => Thaw (ListOf msg Word32) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Word32) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word32 -> m (Mutable s (ListOf msg Word32)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word32) -> m (ListOf msg Word32) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word32 -> m (Mutable s (ListOf msg Word32)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word32) -> m (ListOf msg Word32) Source #

Thaw msg => Thaw (ListOf msg Word16) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Word16) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word16 -> m (Mutable s (ListOf msg Word16)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word16) -> m (ListOf msg Word16) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word16 -> m (Mutable s (ListOf msg Word16)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word16) -> m (ListOf msg Word16) Source #

Thaw msg => Thaw (ListOf msg Word8) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Word8) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word8 -> m (Mutable s (ListOf msg Word8)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word8) -> m (ListOf msg Word8) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Word8 -> m (Mutable s (ListOf msg Word8)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Word8) -> m (ListOf msg Word8) Source #

Thaw msg => Thaw (ListOf msg Bool) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Bool) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Bool -> m (Mutable s (ListOf msg Bool)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Bool) -> m (ListOf msg Bool) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg Bool -> m (Mutable s (ListOf msg Bool)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg Bool) -> m (ListOf msg Bool) Source #

Thaw msg => Thaw (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Mutable s (ListOf msg ()) :: * Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg () -> m (Mutable s (ListOf msg ())) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg ()) -> m (ListOf msg ()) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => ListOf msg () -> m (Mutable s (ListOf msg ())) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (ListOf msg ()) -> m (ListOf msg ()) Source #

MessageDefault (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (ListOf msg (Maybe (Ptr msg))) -> ListOf msg (Maybe (Ptr msg)) Source #

MessageDefault (ListOf msg Word64) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg Word32) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg Word16) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg Word8) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg Bool) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (ListOf msg (Struct msg)) -> ListOf msg (Struct msg) Source #

MessageDefault (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (ListOf msg ()) -> ListOf msg () Source #

HasMessage (ListOf msg a) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type InMessage (ListOf msg a) :: * Source #

Methods

message :: ListOf msg a -> InMessage (ListOf msg a) Source #

type Mutable s (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg (Maybe (Ptr msg))) = ListOf (Mutable s msg) (Maybe (Ptr (Mutable s msg)))
type Mutable s (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg (Struct msg)) = ListOf (Mutable s msg) (Struct (Mutable s msg))
type Mutable s (ListOf msg Word64) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg Word64) = ListOf (Mutable s msg) Word64
type Mutable s (ListOf msg Word32) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg Word32) = ListOf (Mutable s msg) Word32
type Mutable s (ListOf msg Word16) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg Word16) = ListOf (Mutable s msg) Word16
type Mutable s (ListOf msg Word8) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg Word8) = ListOf (Mutable s msg) Word8
type Mutable s (ListOf msg Bool) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg Bool) = ListOf (Mutable s msg) Bool
type Mutable s (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Mutable s (ListOf msg ()) = ListOf (Mutable s msg) ()
type InMessage (ListOf msg a) Source # 
Instance details

Defined in Data.Capnp.Untyped

type InMessage (ListOf msg a) = msg

dataSection :: Struct msg -> ListOf msg Word64 Source #

The data section of a struct, as a list of Word64

ptrSection :: Struct msg -> ListOf msg (Maybe (Ptr msg)) Source #

The pointer section of a struct, as a list of Ptr

getData :: ReadCtx m msg => Int -> Struct msg -> m Word64 Source #

getData i struct gets the ith word from the struct's data section, returning 0 if it is absent.

getPtr :: ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Source #

getPtr i struct gets the ith word from the struct's pointer section, returning Nothing if it is absent.

setData :: (ReadCtx m (MutMsg s), WriteCtx m s) => Word64 -> Int -> Struct (MutMsg s) -> m () Source #

setData value i struct sets the ith word in the struct's data section to value.

setPtr :: (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Source #

setData value i struct sets the ith pointer in the struct's pointer section to value.

copyStruct :: RWCtx m s => Struct (MutMsg s) -> Struct (MutMsg s) -> m () Source #

copyStruct dest src copies the source struct to the destination struct.

get :: ReadCtx m msg => msg -> WordAddr -> m (Maybe (Ptr msg)) Source #

get msg addr returns the Ptr stored at addr in msg. Deducts 1 from the quota for each word read (which may be multiple in the case of far pointers).

index :: ReadCtx m msg => Int -> ListOf msg a -> m a Source #

index i list returns the ith element in list. Deducts 1 from the quota

length :: ListOf msg a -> Int Source #

Returns the length of a list

setIndex :: RWCtx m s => a -> Int -> ListOf (MutMsg s) a -> m () Source #

'setIndex value i list Set the ith element of list to value.

take :: MonadThrow m => Int -> ListOf msg a -> m (ListOf msg a) Source #

Return a prefix of the list, of the given length.

rootPtr :: ReadCtx m msg => msg -> m (Struct msg) Source #

Returns the root pointer of a message.

setRoot :: WriteCtx m s => Struct (MutMsg s) -> m () Source #

Make the given struct the root object of its message.

rawBytes :: ReadCtx m msg => ListOf msg Word8 -> m ByteString Source #

rawBytes returns the raw bytes corresponding to the list.

type ReadCtx m msg = (Message m msg, MonadThrow m, MonadLimit m) Source #

Type (constraint) synonym for the constraints needed for most read operations.

type RWCtx m s = (ReadCtx m (MutMsg s), WriteCtx m s) Source #

Synonym for ReadCtx + WriteCtx

class HasMessage a where Source #

Types a whose storage is owned by a message..

Minimal complete definition

message

Associated Types

type InMessage a Source #

The type of the messages containing as.

Methods

message :: a -> InMessage a Source #

Get the message in which the a is stored.

Instances
HasMessage (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type InMessage (Struct msg) :: * Source #

Methods

message :: Struct msg -> InMessage (Struct msg) Source #

HasMessage (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type InMessage (List msg) :: * Source #

Methods

message :: List msg -> InMessage (List msg) Source #

HasMessage (Ptr msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type InMessage (Ptr msg) :: * Source #

Methods

message :: Ptr msg -> InMessage (Ptr msg) Source #

HasMessage (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type'anyPointer'unconstrained msg) :: * Source #

HasMessage (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type'anyPointer'parameter'group' msg) :: * Source #

HasMessage (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type'anyPointer msg) :: * Source #

HasMessage (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node'Parameter msg) :: * Source #

HasMessage (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node'NestedNode msg) :: * Source #

HasMessage (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node'annotation'group' msg) :: * Source #

HasMessage (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node'const'group' msg) :: * Source #

HasMessage (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node'interface'group' msg) :: * Source #

HasMessage (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node'enum'group' msg) :: * Source #

HasMessage (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node'struct'group' msg) :: * Source #

HasMessage (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node' msg) :: * Source #

Methods

message :: Node' msg -> InMessage (Node' msg) Source #

HasMessage (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Field'ordinal msg) :: * Source #

HasMessage (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Field'group'group' msg) :: * Source #

HasMessage (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Field'slot'group' msg) :: * Source #

HasMessage (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Field' msg) :: * Source #

Methods

message :: Field' msg -> InMessage (Field' msg) Source #

HasMessage (CodeGeneratorRequest'RequestedFile'Import msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (CodeGeneratorRequest'RequestedFile msg) :: * Source #

HasMessage (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Brand'Scope' msg) :: * Source #

HasMessage (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Brand'Scope msg) :: * Source #

HasMessage (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Brand'Binding msg) :: * Source #

HasMessage (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Value msg) :: * Source #

Methods

message :: Value msg -> InMessage (Value msg) Source #

HasMessage (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type'anyPointer'group' msg) :: * Source #

HasMessage (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type'interface'group' msg) :: * Source #

HasMessage (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type'struct'group' msg) :: * Source #

HasMessage (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type'enum'group' msg) :: * Source #

HasMessage (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type'list'group' msg) :: * Source #

HasMessage (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Type msg) :: * Source #

Methods

message :: Type msg -> InMessage (Type msg) Source #

HasMessage (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Superclass msg) :: * Source #

HasMessage (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Node msg) :: * Source #

Methods

message :: Node msg -> InMessage (Node msg) Source #

HasMessage (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Method msg) :: * Source #

Methods

message :: Method msg -> InMessage (Method msg) Source #

HasMessage (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Field msg) :: * Source #

Methods

message :: Field msg -> InMessage (Field msg) Source #

HasMessage (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Enumerant msg) :: * Source #

Methods

message :: Enumerant msg -> InMessage (Enumerant msg) Source #

HasMessage (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (CodeGeneratorRequest msg) :: * Source #

HasMessage (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (CapnpVersion msg) :: * Source #

HasMessage (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Brand msg) :: * Source #

Methods

message :: Brand msg -> InMessage (Brand msg) Source #

HasMessage (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type InMessage (Annotation msg) :: * Source #

HasMessage (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type InMessage (VatId msg) :: * Source #

Methods

message :: VatId msg -> InMessage (VatId msg) Source #

HasMessage (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type InMessage (ProvisionId msg) :: * Source #

HasMessage (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type InMessage (JoinResult msg) :: * Source #

HasMessage (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type InMessage (JoinKeyPart msg) :: * Source #

HasMessage (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Return' msg) :: * Source #

Methods

message :: Return' msg -> InMessage (Return' msg) Source #

HasMessage (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Resolve' msg) :: * Source #

Methods

message :: Resolve' msg -> InMessage (Resolve' msg) Source #

HasMessage (PromisedAnswer'Op msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (PromisedAnswer'Op msg) :: * Source #

HasMessage (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Disembargo'context msg) :: * Source #

HasMessage (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Call'sendResultsTo msg) :: * Source #

HasMessage (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (ThirdPartyCapDescriptor msg) :: * Source #

HasMessage (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Return msg) :: * Source #

Methods

message :: Return msg -> InMessage (Return msg) Source #

HasMessage (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Resolve msg) :: * Source #

Methods

message :: Resolve msg -> InMessage (Resolve msg) Source #

HasMessage (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Release msg) :: * Source #

Methods

message :: Release msg -> InMessage (Release msg) Source #

HasMessage (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Provide msg) :: * Source #

Methods

message :: Provide msg -> InMessage (Provide msg) Source #

HasMessage (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (PromisedAnswer msg) :: * Source #

HasMessage (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Payload msg) :: * Source #

Methods

message :: Payload msg -> InMessage (Payload msg) Source #

HasMessage (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (MessageTarget msg) :: * Source #

HasMessage (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Message msg) :: * Source #

Methods

message :: Message msg -> InMessage (Message msg) Source #

HasMessage (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Join msg) :: * Source #

Methods

message :: Join msg -> InMessage (Join msg) Source #

HasMessage (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Finish msg) :: * Source #

Methods

message :: Finish msg -> InMessage (Finish msg) Source #

HasMessage (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Exception msg) :: * Source #

Methods

message :: Exception msg -> InMessage (Exception msg) Source #

HasMessage (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Disembargo msg) :: * Source #

HasMessage (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (CapDescriptor msg) :: * Source #

HasMessage (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Call msg) :: * Source #

Methods

message :: Call msg -> InMessage (Call msg) Source #

HasMessage (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Bootstrap msg) :: * Source #

Methods

message :: Bootstrap msg -> InMessage (Bootstrap msg) Source #

HasMessage (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

type InMessage (Accept msg) :: * Source #

Methods

message :: Accept msg -> InMessage (Accept msg) Source #

HasMessage (Persistent'SaveResults msg) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Associated Types

type InMessage (Persistent'SaveResults msg) :: * Source #

HasMessage (Persistent'SaveParams msg) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Associated Types

type InMessage (Persistent'SaveParams msg) :: * Source #

HasMessage (JsonValue'Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Associated Types

type InMessage (JsonValue'Field msg) :: * Source #

HasMessage (JsonValue'Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Associated Types

type InMessage (JsonValue'Call msg) :: * Source #

HasMessage (JsonValue msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Associated Types

type InMessage (JsonValue msg) :: * Source #

Methods

message :: JsonValue msg -> InMessage (JsonValue msg) Source #

HasMessage (ListOf msg a) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type InMessage (ListOf msg a) :: * Source #

Methods

message :: ListOf msg a -> InMessage (ListOf msg a) Source #

class HasMessage a => MessageDefault a where Source #

Types which have a "default" value, but require a message to construct it.

The default is usually conceptually zero-size. This is mostly useful for generated code, so that it can use standard decoding techniques on default values.

Minimal complete definition

messageDefault

Methods

messageDefault :: InMessage a -> a Source #

Instances
MessageDefault (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (Struct msg) -> Struct msg Source #

MessageDefault (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: InMessage (Node' msg) -> Node' msg Source #

MessageDefault (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: InMessage (Field' msg) -> Field' msg Source #

MessageDefault (CodeGeneratorRequest'RequestedFile'Import msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: InMessage (Value msg) -> Value msg Source #

MessageDefault (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: InMessage (Type msg) -> Type msg Source #

MessageDefault (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: InMessage (Node msg) -> Node msg Source #

MessageDefault (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: InMessage (Method msg) -> Method msg Source #

MessageDefault (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: InMessage (Field msg) -> Field msg Source #

MessageDefault (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: InMessage (Brand msg) -> Brand msg Source #

MessageDefault (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

messageDefault :: InMessage (VatId msg) -> VatId msg Source #

MessageDefault (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

MessageDefault (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

MessageDefault (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

MessageDefault (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (PromisedAnswer'Op msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: InMessage (Return msg) -> Return msg Source #

MessageDefault (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: InMessage (Join msg) -> Join msg Source #

MessageDefault (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: InMessage (Finish msg) -> Finish msg Source #

MessageDefault (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: InMessage (Call msg) -> Call msg Source #

MessageDefault (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: InMessage (Accept msg) -> Accept msg Source #

MessageDefault (Persistent'SaveResults msg) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

MessageDefault (Persistent'SaveParams msg) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

MessageDefault (JsonValue'Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

MessageDefault (JsonValue'Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

MessageDefault (JsonValue msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

MessageDefault (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (ListOf msg (Maybe (Ptr msg))) -> ListOf msg (Maybe (Ptr msg)) Source #

MessageDefault (ListOf msg Word64) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg Word32) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg Word16) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg Word8) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg Bool) Source # 
Instance details

Defined in Data.Capnp.Untyped

MessageDefault (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (ListOf msg (Struct msg)) -> ListOf msg (Struct msg) Source #

MessageDefault (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: InMessage (ListOf msg ()) -> ListOf msg () Source #

allocStruct :: WriteCtx m s => MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) Source #

Allocate a struct in the message.

allocCompositeList Source #

Arguments

:: WriteCtx m s 
=> MutMsg s

The message to allocate in.

-> Word16

The size of the data sections

-> Word16

The size of the pointer sections

-> Int

The length of the list in elements.

-> m (ListOf (MutMsg s) (Struct (MutMsg s))) 

Allocate a composite list.

allocList0 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) ()) Source #

Allocate a list of capnproto Void values.

allocList1 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Bool) Source #

Allocate a list of booleans

allocList8 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word8) Source #

Allocate a list of 8-bit values.

allocList16 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word16) Source #

Allocate a list of 16-bit values.

allocList32 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word32) Source #

Allocate a list of 32-bit values.

allocList64 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word64) Source #

Allocate a list of 64-bit words.

allocListPtr :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) (Maybe (Ptr (MutMsg s)))) Source #

Allocate a list of pointers.