capnp-0.1.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 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 #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (Ptr msg) :: * Source #

type Frozen (Ptr msg) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Ptr msg)) => Frozen (Ptr msg) -> m (Ptr msg) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Ptr msg)) => Ptr msg -> m (Frozen (Ptr msg)) Source #

HasMessage (Ptr msg) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

message :: Ptr msg -> msg Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg (Maybe (Ptr msg))) :: * Source #

type Frozen (ListOf msg (Maybe (Ptr msg))) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Maybe (Ptr msg)))) => Frozen (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Maybe (Ptr msg)))) => ListOf msg (Maybe (Ptr msg)) -> m (Frozen (ListOf msg (Maybe (Ptr msg)))) Source #

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

Defined in Data.Capnp.Untyped

Methods

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

type Scope (Ptr msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Scope (Ptr msg) = Scope msg
type Frozen (Ptr msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Frozen (Ptr msg) = Ptr (Frozen msg)
type Scope (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Scope (ListOf msg (Maybe (Ptr msg))) = Scope msg
type Frozen (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Frozen (ListOf msg (Maybe (Ptr msg))) = ListOf (Frozen msg) (Maybe (Ptr (Frozen 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
Mutable msg => Mutable (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (List msg) :: * Source #

type Frozen (List msg) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (List msg)) => Frozen (List msg) -> m (List msg) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (List msg)) => List msg -> m (Frozen (List msg)) Source #

HasMessage (List msg) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

message :: List msg -> msg Source #

type Scope (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Scope (List msg) = Scope msg
type Frozen (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Frozen (List msg) = List (Frozen 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 #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (Struct msg) :: * Source #

type Frozen (Struct msg) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Struct msg)) => Frozen (Struct msg) -> m (Struct msg) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Struct msg)) => Struct msg -> m (Frozen (Struct msg)) Source #

MessageDefault (Struct msg) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> Struct msg Source #

HasMessage (Struct msg) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

message :: Struct msg -> msg Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg (Struct msg)) :: * Source #

type Frozen (ListOf msg (Struct msg)) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Struct msg))) => Frozen (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Struct msg))) => ListOf msg (Struct msg) -> m (Frozen (ListOf msg (Struct msg))) Source #

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

Defined in Data.Capnp.Untyped

Methods

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

type Scope (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Scope (Struct msg) = Scope msg
type Frozen (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Frozen (Struct msg) = Struct (Frozen msg)
type Scope (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Scope (ListOf msg (Struct msg)) = Scope msg
type Frozen (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Frozen (ListOf msg (Struct msg)) = ListOf (Frozen msg) (Struct (Frozen 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 #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg (Maybe (Ptr msg))) :: * Source #

type Frozen (ListOf msg (Maybe (Ptr msg))) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Maybe (Ptr msg)))) => Frozen (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Maybe (Ptr msg)))) => ListOf msg (Maybe (Ptr msg)) -> m (Frozen (ListOf msg (Maybe (Ptr msg)))) Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg (Struct msg)) :: * Source #

type Frozen (ListOf msg (Struct msg)) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Struct msg))) => Frozen (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Struct msg))) => ListOf msg (Struct msg) -> m (Frozen (ListOf msg (Struct msg))) Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Word64) :: * Source #

type Frozen (ListOf msg Word64) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word64)) => Frozen (ListOf msg Word64) -> m (ListOf msg Word64) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word64)) => ListOf msg Word64 -> m (Frozen (ListOf msg Word64)) Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Word32) :: * Source #

type Frozen (ListOf msg Word32) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word32)) => Frozen (ListOf msg Word32) -> m (ListOf msg Word32) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word32)) => ListOf msg Word32 -> m (Frozen (ListOf msg Word32)) Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Word16) :: * Source #

type Frozen (ListOf msg Word16) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word16)) => Frozen (ListOf msg Word16) -> m (ListOf msg Word16) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word16)) => ListOf msg Word16 -> m (Frozen (ListOf msg Word16)) Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Word8) :: * Source #

type Frozen (ListOf msg Word8) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word8)) => Frozen (ListOf msg Word8) -> m (ListOf msg Word8) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word8)) => ListOf msg Word8 -> m (Frozen (ListOf msg Word8)) Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Bool) :: * Source #

type Frozen (ListOf msg Bool) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Bool)) => Frozen (ListOf msg Bool) -> m (ListOf msg Bool) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Bool)) => ListOf msg Bool -> m (Frozen (ListOf msg Bool)) Source #

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg ()) :: * Source #

type Frozen (ListOf msg ()) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg ())) => Frozen (ListOf msg ()) -> m (ListOf msg ()) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg ())) => ListOf msg () -> m (Frozen (ListOf msg ())) Source #

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

Defined in Data.Capnp.Untyped

Methods

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

MessageDefault (ListOf msg Word64) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Word64 Source #

MessageDefault (ListOf msg Word32) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Word32 Source #

MessageDefault (ListOf msg Word16) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Word16 Source #

MessageDefault (ListOf msg Word8) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Word8 Source #

MessageDefault (ListOf msg Bool) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Bool Source #

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

Defined in Data.Capnp.Untyped

Methods

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

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

Defined in Data.Capnp.Untyped

Methods

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

HasMessage (ListOf msg a) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

message :: ListOf msg a -> msg Source #

type Scope (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

type Scope (ListOf msg Bool) = Scope msg
type Scope (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Scope (ListOf msg ()) = Scope msg
type Frozen (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

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

Defined in Data.Capnp.Untyped

type Frozen (ListOf msg Bool) = ListOf (Frozen msg) Bool
type Frozen (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Untyped

type Frozen (ListOf msg ()) = ListOf (Frozen 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 :: (ReadCtx m (MutMsg s), WriteCtx 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 :: (ReadCtx m (MutMsg s), WriteCtx 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 msg where Source #

Types a whose storage is owned by a message with blob type b.

Minimal complete definition

message

Methods

message :: a -> msg Source #

Get the message in which the a is stored.

Instances
HasMessage (Struct msg) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

message :: Struct msg -> msg Source #

HasMessage (List msg) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

message :: List msg -> msg Source #

HasMessage (Ptr msg) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

message :: Ptr msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

message :: Type'anyPointer msg -> msg Source #

HasMessage (Node'Parameter msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'Parameter msg -> msg Source #

HasMessage (Node'NestedNode msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'NestedNode msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Node'annotation'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Node'const'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Node'interface'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Node'enum'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Node'struct'group' msg -> msg Source #

HasMessage (Node' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Field'ordinal msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Field'group'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Field'slot'group' msg -> msg Source #

HasMessage (Field' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Field' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

message :: Brand'Scope' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Brand'Scope msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Brand'Binding msg -> msg Source #

HasMessage (Value msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Value msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Type'anyPointer'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Type'interface'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Type'struct'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Type'enum'group' msg -> msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

message :: Type'list'group' msg -> msg Source #

HasMessage (Type msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Type msg -> msg Source #

HasMessage (Superclass msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Superclass msg -> msg Source #

HasMessage (Node msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node msg -> msg Source #

HasMessage (Method msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Method msg -> msg Source #

HasMessage (Field msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Field msg -> msg Source #

HasMessage (Enumerant msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Enumerant msg -> msg Source #

HasMessage (CodeGeneratorRequest msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: CodeGeneratorRequest msg -> msg Source #

HasMessage (CapnpVersion msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: CapnpVersion msg -> msg Source #

HasMessage (Brand msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Brand msg -> msg Source #

HasMessage (Annotation msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Annotation msg -> msg Source #

HasMessage (VatId msg) msg Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

message :: VatId msg -> msg Source #

HasMessage (ProvisionId msg) msg Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

message :: ProvisionId msg -> msg Source #

HasMessage (JoinResult msg) msg Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

message :: JoinResult msg -> msg Source #

HasMessage (JoinKeyPart msg) msg Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

message :: JoinKeyPart msg -> msg Source #

HasMessage (Return' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Return' msg -> msg Source #

HasMessage (Resolve' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Resolve' msg -> msg Source #

HasMessage (PromisedAnswer'Op msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: PromisedAnswer'Op msg -> msg Source #

HasMessage (Disembargo'context msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Disembargo'context msg -> msg Source #

HasMessage (Call'sendResultsTo msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Call'sendResultsTo msg -> msg Source #

HasMessage (ThirdPartyCapDescriptor msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

HasMessage (Return msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Return msg -> msg Source #

HasMessage (Resolve msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Resolve msg -> msg Source #

HasMessage (Release msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Release msg -> msg Source #

HasMessage (Provide msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Provide msg -> msg Source #

HasMessage (PromisedAnswer msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: PromisedAnswer msg -> msg Source #

HasMessage (Payload msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Payload msg -> msg Source #

HasMessage (MessageTarget msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: MessageTarget msg -> msg Source #

HasMessage (Message msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Message msg -> msg Source #

HasMessage (Join msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Join msg -> msg Source #

HasMessage (Finish msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Finish msg -> msg Source #

HasMessage (Exception msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Exception msg -> msg Source #

HasMessage (Disembargo msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Disembargo msg -> msg Source #

HasMessage (CapDescriptor msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: CapDescriptor msg -> msg Source #

HasMessage (Call msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Call msg -> msg Source #

HasMessage (Bootstrap msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Bootstrap msg -> msg Source #

HasMessage (Accept msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Accept msg -> msg Source #

HasMessage (Persistent'SaveResults msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Methods

message :: Persistent'SaveResults msg -> msg Source #

HasMessage (Persistent'SaveParams msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Methods

message :: Persistent'SaveParams msg -> msg Source #

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

Defined in Capnp.Capnp.Json

Methods

message :: JsonValue'Field msg -> msg Source #

HasMessage (JsonValue'Call msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

message :: JsonValue'Call msg -> msg Source #

HasMessage (JsonValue msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

message :: JsonValue msg -> msg Source #

HasMessage (ListOf msg a) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

message :: ListOf msg a -> msg Source #

class HasMessage a msg => MessageDefault a msg 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 :: msg -> a Source #

Instances
MessageDefault (Struct msg) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> Struct msg Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Type'anyPointer msg Source #

MessageDefault (Node'Parameter msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Node'Parameter msg Source #

MessageDefault (Node'NestedNode msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Node'NestedNode msg Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

MessageDefault (Node' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Node' msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Field'ordinal msg Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

MessageDefault (Field' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Field' msg Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Brand'Scope' msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Brand'Scope msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Brand'Binding msg Source #

MessageDefault (Value msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Value msg Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

MessageDefault (Type msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Type msg Source #

MessageDefault (Superclass msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Superclass msg Source #

MessageDefault (Node msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Node msg Source #

MessageDefault (Method msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Method msg Source #

MessageDefault (Field msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Field msg Source #

MessageDefault (Enumerant msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Enumerant msg Source #

MessageDefault (CodeGeneratorRequest msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (CapnpVersion msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> CapnpVersion msg Source #

MessageDefault (Brand msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Brand msg Source #

MessageDefault (Annotation msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Annotation msg Source #

MessageDefault (VatId msg) msg Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

messageDefault :: msg -> VatId msg Source #

MessageDefault (ProvisionId msg) msg Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

messageDefault :: msg -> ProvisionId msg Source #

MessageDefault (JoinResult msg) msg Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

messageDefault :: msg -> JoinResult msg Source #

MessageDefault (JoinKeyPart msg) msg Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

messageDefault :: msg -> JoinKeyPart msg Source #

MessageDefault (Return' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Return' msg Source #

MessageDefault (Resolve' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Resolve' msg Source #

MessageDefault (PromisedAnswer'Op msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Disembargo'context msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Call'sendResultsTo msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (ThirdPartyCapDescriptor msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MessageDefault (Return msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Return msg Source #

MessageDefault (Resolve msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Resolve msg Source #

MessageDefault (Release msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Release msg Source #

MessageDefault (Provide msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Provide msg Source #

MessageDefault (PromisedAnswer msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> PromisedAnswer msg Source #

MessageDefault (Payload msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Payload msg Source #

MessageDefault (MessageTarget msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> MessageTarget msg Source #

MessageDefault (Message msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Message msg Source #

MessageDefault (Join msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Join msg Source #

MessageDefault (Finish msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Finish msg Source #

MessageDefault (Exception msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Exception msg Source #

MessageDefault (Disembargo msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Disembargo msg Source #

MessageDefault (CapDescriptor msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> CapDescriptor msg Source #

MessageDefault (Call msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Call msg Source #

MessageDefault (Bootstrap msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Bootstrap msg Source #

MessageDefault (Accept msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Accept msg Source #

MessageDefault (Persistent'SaveResults msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Persistent

MessageDefault (Persistent'SaveParams msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Persistent

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

Defined in Capnp.Capnp.Json

Methods

messageDefault :: msg -> JsonValue'Field msg Source #

MessageDefault (JsonValue'Call msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

messageDefault :: msg -> JsonValue'Call msg Source #

MessageDefault (JsonValue msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

messageDefault :: msg -> JsonValue msg Source #

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

Defined in Data.Capnp.Untyped

Methods

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

MessageDefault (ListOf msg Word64) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Word64 Source #

MessageDefault (ListOf msg Word32) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Word32 Source #

MessageDefault (ListOf msg Word16) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Word16 Source #

MessageDefault (ListOf msg Word8) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Word8 Source #

MessageDefault (ListOf msg Bool) msg Source # 
Instance details

Defined in Data.Capnp.Untyped

Methods

messageDefault :: msg -> ListOf msg Bool Source #

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

Defined in Data.Capnp.Untyped

Methods

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

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

Defined in Data.Capnp.Untyped

Methods

messageDefault :: 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.