capnp-0.6.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.Untyped

Contents

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 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 (Cap msg) 
PtrList (List msg) 
PtrStruct (Struct msg) 
Instances
TraverseMsg Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Ptr msgA -> m (Ptr msgB) Source #

ToPtr s (Maybe (Ptr (MutMsg s))) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> Maybe (Ptr (MutMsg s)) -> m (Maybe (Ptr (MutMsg s))) Source #

FromPtr msg (Maybe (Ptr msg)) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) (Maybe (Ptr (MutMsg s)))) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

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

Defined in Capnp.Classes

Methods

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

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

Defined in Capnp.Untyped

Associated Types

type Mutable s (Ptr msg) :: Type 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 Capnp.Untyped

Associated Types

type InMessage (Ptr msg) :: Type Source #

Methods

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

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

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf msg (Maybe (Ptr msg))) :: Type 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 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 Capnp.Untyped

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

Defined in 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 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
TraverseMsg List Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> List msgA -> m (List msgB) Source #

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

Defined in Capnp.Untyped

Associated Types

type Mutable s (List msg) :: Type 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 Capnp.Untyped

Associated Types

type InMessage (List msg) :: Type Source #

Methods

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

type Mutable s (List msg) Source # 
Instance details

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

type InMessage (List msg) = msg

data Struct msg Source #

A struct value in a message.

Instances
TraverseMsg Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Struct msgA -> m (Struct msgB) Source #

ToStruct msg (Struct msg) Source # 
Instance details

Defined in Capnp.Classes

Methods

toStruct :: Struct msg -> Struct msg Source #

FromStruct msg (Struct msg) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (Struct (MutMsg s)) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> Struct (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

FromPtr msg (Struct msg) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) (Struct (MutMsg s))) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> ListOf (MutMsg s) (Struct (MutMsg s)) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Classes

Methods

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

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

Defined in Capnp.Untyped

Associated Types

type Mutable s (Struct msg) :: Type 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 Capnp.Untyped

Methods

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

HasMessage (Struct msg) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type InMessage (Struct msg) :: Type Source #

Methods

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

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

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf msg (Struct msg)) :: Type 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 Capnp.Untyped

Methods

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

type Mutable s (Struct msg) Source # 
Instance details

Defined in Capnp.Untyped

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

Defined in 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 Capnp.Untyped

type InMessage (Struct msg) = msg

data ListOf msg a Source #

A list of values of type a in a message.

Instances
ToPtr s (ListOf (MutMsg s) (Maybe (Ptr (MutMsg s)))) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) (Struct (MutMsg s))) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> ListOf (MutMsg s) (Struct (MutMsg s)) -> m (Maybe (Ptr (MutMsg s))) Source #

ToPtr s (ListOf (MutMsg s) Bool) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> ListOf (MutMsg s) Bool -> m (Maybe (Ptr (MutMsg s))) Source #

ToPtr s (ListOf (MutMsg s) Word64) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> ListOf (MutMsg s) Word64 -> m (Maybe (Ptr (MutMsg s))) Source #

ToPtr s (ListOf (MutMsg s) Word32) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> ListOf (MutMsg s) Word32 -> m (Maybe (Ptr (MutMsg s))) Source #

ToPtr s (ListOf (MutMsg s) Word16) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> ListOf (MutMsg s) Word16 -> m (Maybe (Ptr (MutMsg s))) Source #

ToPtr s (ListOf (MutMsg s) Word8) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> ListOf (MutMsg s) Word8 -> m (Maybe (Ptr (MutMsg s))) Source #

ToPtr s (ListOf (MutMsg s) ()) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

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

Defined in Capnp.Classes

Methods

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

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

Defined in Capnp.Classes

Methods

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

FromPtr msg (ListOf msg Bool) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

FromPtr msg (ListOf msg Word64) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

FromPtr msg (ListOf msg Word32) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

FromPtr msg (ListOf msg Word16) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

FromPtr msg (ListOf msg Word8) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

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

Defined in Capnp.Classes

Methods

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

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

Defined in Capnp.Untyped

Associated Types

type Mutable s (ListOf msg (Maybe (Ptr msg))) :: Type 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 Capnp.Untyped

Associated Types

type Mutable s (ListOf msg (Struct msg)) :: Type 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 Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Word64) :: Type 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 Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Word32) :: Type 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 Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Word16) :: Type 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 Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Word8) :: Type 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 Capnp.Untyped

Associated Types

type Mutable s (ListOf msg Bool) :: Type 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 Capnp.Untyped

Associated Types

type Mutable s (ListOf msg ()) :: Type 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 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 Capnp.Untyped

MessageDefault (ListOf msg Word32) Source # 
Instance details

Defined in Capnp.Untyped

MessageDefault (ListOf msg Word16) Source # 
Instance details

Defined in Capnp.Untyped

MessageDefault (ListOf msg Word8) Source # 
Instance details

Defined in Capnp.Untyped

MessageDefault (ListOf msg Bool) Source # 
Instance details

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

Methods

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

MessageDefault (ListOf msg ()) Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

HasMessage (ListOf msg a) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

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

Methods

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

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

Defined in 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 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 Capnp.Untyped

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

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

type InMessage (ListOf msg a) = msg

data Cap msg Source #

A Capability in a message.

Instances
TraverseMsg Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Cap msgA -> m (Cap msgB) Source #

ToPtr s (Maybe (Cap (MutMsg s))) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> Maybe (Cap (MutMsg s)) -> m (Maybe (Ptr (MutMsg s))) Source #

FromPtr msg (Maybe (Cap msg)) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

HasMessage (Cap msg) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type InMessage (Cap msg) :: Type Source #

Methods

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

type InMessage (Cap msg) Source # 
Instance details

Defined in Capnp.Untyped

type InMessage (Cap msg) = msg

structByteCount :: Struct msg -> ByteCount Source #

Get the size (in bytes) of a struct's data section.

structWordCount :: Struct msg -> WordCount Source #

Get the size (in words) of a struct's data section.

structPtrCount :: Struct msg -> Word16 Source #

Get the size of a struct's pointer section.

structListByteCount :: ListOf msg (Struct msg) -> ByteCount Source #

Get the size (in words) of the data sections in a struct list.

structListWordCount :: ListOf msg (Struct msg) -> WordCount Source #

Get the size (in words) of the data sections in a struct list.

structListPtrCount :: ListOf msg (Struct msg) -> Word16 Source #

Get the size of the pointer sections in a struct list.

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.

getClient :: ReadCtx m msg => Cap msg -> m Client Source #

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

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 Capnp.Untyped

Associated Types

type InMessage (Struct msg) :: Type Source #

Methods

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

HasMessage (Cap msg) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type InMessage (Cap msg) :: Type Source #

Methods

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

HasMessage (List msg) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type InMessage (List msg) :: Type Source #

Methods

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

HasMessage (Ptr msg) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type InMessage (Ptr msg) :: Type Source #

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

HasMessage (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

HasMessage (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (CodeGeneratorRequest msg) :: Type Source #

HasMessage (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (CapnpVersion msg) :: Type Source #

HasMessage (Annotation msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Annotation msg) :: Type Source #

HasMessage (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Value msg) :: Type Source #

Methods

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

HasMessage (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Brand msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Brand msg) :: Type Source #

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Type'interface msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Type'struct msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Type'enum msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

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

HasMessage (Type'list msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

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

HasMessage (Type msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Type msg) :: Type Source #

Methods

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

HasMessage (Method msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Method msg) :: Type Source #

Methods

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

HasMessage (Superclass msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Superclass msg) :: Type Source #

HasMessage (Enumerant msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Enumerant msg) :: Type Source #

Methods

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

HasMessage (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Field'group msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Field'slot msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Field'slot msg) :: Type Source #

HasMessage (Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Field msg) :: Type Source #

Methods

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

HasMessage (Node'SourceInfo'Member msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Node'SourceInfo'Member msg) :: Type Source #

HasMessage (Node'SourceInfo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Node'SourceInfo msg) :: Type Source #

HasMessage (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

HasMessage (Node'annotation msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Node'annotation msg) :: Type Source #

HasMessage (Node'const msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Node'const msg) :: Type Source #

HasMessage (Node'interface msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Node'interface msg) :: Type Source #

HasMessage (Node'enum msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Node'enum msg) :: Type Source #

Methods

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

HasMessage (Node'struct msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Node'struct msg) :: Type Source #

HasMessage (Node msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type InMessage (Node msg) :: Type Source #

Methods

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

HasMessage (JoinResult msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (JoinResult msg) :: Type Source #

HasMessage (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (JoinKeyPart msg) :: Type Source #

HasMessage (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (ThirdPartyCapId msg) :: Type Source #

HasMessage (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (RecipientId msg) :: Type Source #

HasMessage (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (ProvisionId msg) :: Type Source #

HasMessage (VatId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (VatId msg) :: Type Source #

Methods

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

HasMessage (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Exception msg) :: Type Source #

Methods

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

HasMessage (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (ThirdPartyCapDescriptor msg) :: Type Source #

HasMessage (PromisedAnswer'Op msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

HasMessage (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (PromisedAnswer msg) :: Type Source #

HasMessage (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (CapDescriptor msg) :: Type Source #

HasMessage (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Payload msg) :: Type Source #

Methods

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

HasMessage (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (MessageTarget msg) :: Type Source #

HasMessage (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Join msg) :: Type Source #

Methods

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

HasMessage (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Accept msg) :: Type Source #

Methods

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

HasMessage (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Provide msg) :: Type Source #

Methods

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

HasMessage (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

HasMessage (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Disembargo msg) :: Type Source #

HasMessage (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Release msg) :: Type Source #

Methods

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

HasMessage (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Resolve msg) :: Type Source #

Methods

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

HasMessage (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Finish msg) :: Type Source #

Methods

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

HasMessage (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Return msg) :: Type Source #

Methods

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

HasMessage (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

HasMessage (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Call msg) :: Type Source #

Methods

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

HasMessage (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Bootstrap msg) :: Type Source #

Methods

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

HasMessage (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Message msg) :: Type Source #

Methods

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

HasMessage (RealmGateway'export'params msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

type InMessage (RealmGateway'export'params msg) :: Type Source #

HasMessage (RealmGateway'import'params msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

type InMessage (RealmGateway'import'params msg) :: Type Source #

HasMessage (Persistent'SaveResults msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

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

HasMessage (Persistent'SaveParams msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

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

HasMessage (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Associated Types

type InMessage (DiscriminatorOptions msg) :: Type Source #

HasMessage (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Associated Types

type InMessage (FlattenOptions msg) :: Type Source #

HasMessage (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Associated Types

type InMessage (Value'Call msg) :: Type Source #

HasMessage (Value'Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Associated Types

type InMessage (Value'Field msg) :: Type Source #

HasMessage (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Associated Types

type InMessage (Value msg) :: Type Source #

Methods

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

HasMessage (ListOf msg a) Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type InMessage (ListOf msg a) :: Type 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.

Methods

messageDefault :: InMessage a -> a Source #

Instances
MessageDefault (Struct msg) Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Annotation msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Brand msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Type'interface msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Type'struct msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Type'enum msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Type'list msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Type msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Method msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Superclass msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Enumerant msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Field'group msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Field'slot msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Node'SourceInfo'Member msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node'SourceInfo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node'annotation msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node'const msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node'interface msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node'enum msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node'struct msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

MessageDefault (Node msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (JoinResult msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

MessageDefault (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

MessageDefault (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

MessageDefault (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

MessageDefault (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

MessageDefault (VatId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

MessageDefault (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (PromisedAnswer'Op msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

MessageDefault (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

MessageDefault (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

MessageDefault (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

MessageDefault (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

MessageDefault (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

MessageDefault (RealmGateway'export'params msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

MessageDefault (RealmGateway'import'params msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

MessageDefault (Persistent'SaveResults msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

MessageDefault (Persistent'SaveParams msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

MessageDefault (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

MessageDefault (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

MessageDefault (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

MessageDefault (Value'Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

MessageDefault (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

Defined in 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 Capnp.Untyped

MessageDefault (ListOf msg Word32) Source # 
Instance details

Defined in Capnp.Untyped

MessageDefault (ListOf msg Word16) Source # 
Instance details

Defined in Capnp.Untyped

MessageDefault (ListOf msg Word8) Source # 
Instance details

Defined in Capnp.Untyped

MessageDefault (ListOf msg Bool) Source # 
Instance details

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

Methods

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

MessageDefault (ListOf msg ()) Source # 
Instance details

Defined in 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.

appendCap :: WriteCtx m s => MutMsg s -> Client -> m (Cap (MutMsg s)) Source #

class TraverseMsg f where Source #

TraverseMsg is basically Traversable from the prelude, but the intent is that rather than conceptually being a "container", the instance is a value backed by a message, and the point of the type class is to be able to apply transformations to the underlying message.

We don't just use Traversable for this because while algebraically it makes sense, it would be very unintuitive to e.g. have the Traversable instance for List not traverse over the *elements* of the list.

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> f msgA -> m (f msgB) Source #

Instances
TraverseMsg Struct Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Struct msgA -> m (Struct msgB) Source #

TraverseMsg Cap Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Cap msgA -> m (Cap msgB) Source #

TraverseMsg List Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> List msgA -> m (List msgB) Source #

TraverseMsg Ptr Source # 
Instance details

Defined in Capnp.Untyped

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Ptr msgA -> m (Ptr msgB) Source #

TraverseMsg CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

TraverseMsg CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

TraverseMsg CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> CodeGeneratorRequest msgA -> m (CodeGeneratorRequest msgB) Source #

TraverseMsg CapnpVersion Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> CapnpVersion msgA -> m (CapnpVersion msgB) Source #

TraverseMsg Annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Annotation msgA -> m (Annotation msgB) Source #

TraverseMsg Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Value msgA -> m (Value msgB) Source #

TraverseMsg Brand'Binding Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Brand'Binding msgA -> m (Brand'Binding msgB) Source #

TraverseMsg Brand'Scope Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Brand'Scope msgA -> m (Brand'Scope msgB) Source #

TraverseMsg Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Brand msgA -> m (Brand msgB) Source #

TraverseMsg Type'anyPointer'implicitMethodParameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

TraverseMsg Type'anyPointer'parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Type'anyPointer'parameter msgA -> m (Type'anyPointer'parameter msgB) Source #

TraverseMsg Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Type'anyPointer'unconstrained msgA -> m (Type'anyPointer'unconstrained msgB) Source #

TraverseMsg Type'anyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Type'anyPointer msgA -> m (Type'anyPointer msgB) Source #

TraverseMsg Type'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Type'interface msgA -> m (Type'interface msgB) Source #

TraverseMsg Type'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Type'struct msgA -> m (Type'struct msgB) Source #

TraverseMsg Type'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Type'enum msgA -> m (Type'enum msgB) Source #

TraverseMsg Type'list Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Type'list msgA -> m (Type'list msgB) Source #

TraverseMsg Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Type msgA -> m (Type msgB) Source #

TraverseMsg Method Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Method msgA -> m (Method msgB) Source #

TraverseMsg Superclass Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Superclass msgA -> m (Superclass msgB) Source #

TraverseMsg Enumerant Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Enumerant msgA -> m (Enumerant msgB) Source #

TraverseMsg Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Field'ordinal msgA -> m (Field'ordinal msgB) Source #

TraverseMsg Field'group Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Field'group msgA -> m (Field'group msgB) Source #

TraverseMsg Field'slot Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Field'slot msgA -> m (Field'slot msgB) Source #

TraverseMsg Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Field msgA -> m (Field msgB) Source #

TraverseMsg Node'SourceInfo'Member Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'SourceInfo'Member msgA -> m (Node'SourceInfo'Member msgB) Source #

TraverseMsg Node'SourceInfo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'SourceInfo msgA -> m (Node'SourceInfo msgB) Source #

TraverseMsg Node'NestedNode Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'NestedNode msgA -> m (Node'NestedNode msgB) Source #

TraverseMsg Node'Parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'Parameter msgA -> m (Node'Parameter msgB) Source #

TraverseMsg Node'annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'annotation msgA -> m (Node'annotation msgB) Source #

TraverseMsg Node'const Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'const msgA -> m (Node'const msgB) Source #

TraverseMsg Node'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'interface msgA -> m (Node'interface msgB) Source #

TraverseMsg Node'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'enum msgA -> m (Node'enum msgB) Source #

TraverseMsg Node'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node'struct msgA -> m (Node'struct msgB) Source #

TraverseMsg Node Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Node msgA -> m (Node msgB) Source #

TraverseMsg JoinResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> JoinResult msgA -> m (JoinResult msgB) Source #

TraverseMsg JoinKeyPart Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> JoinKeyPart msgA -> m (JoinKeyPart msgB) Source #

TraverseMsg ThirdPartyCapId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> ThirdPartyCapId msgA -> m (ThirdPartyCapId msgB) Source #

TraverseMsg RecipientId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> RecipientId msgA -> m (RecipientId msgB) Source #

TraverseMsg ProvisionId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> ProvisionId msgA -> m (ProvisionId msgB) Source #

TraverseMsg VatId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> VatId msgA -> m (VatId msgB) Source #

TraverseMsg Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Exception msgA -> m (Exception msgB) Source #

TraverseMsg ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> ThirdPartyCapDescriptor msgA -> m (ThirdPartyCapDescriptor msgB) Source #

TraverseMsg PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> PromisedAnswer'Op msgA -> m (PromisedAnswer'Op msgB) Source #

TraverseMsg PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> PromisedAnswer msgA -> m (PromisedAnswer msgB) Source #

TraverseMsg CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> CapDescriptor msgA -> m (CapDescriptor msgB) Source #

TraverseMsg Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Payload msgA -> m (Payload msgB) Source #

TraverseMsg MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> MessageTarget msgA -> m (MessageTarget msgB) Source #

TraverseMsg Join Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Join msgA -> m (Join msgB) Source #

TraverseMsg Accept Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Accept msgA -> m (Accept msgB) Source #

TraverseMsg Provide Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Provide msgA -> m (Provide msgB) Source #

TraverseMsg Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Disembargo'context msgA -> m (Disembargo'context msgB) Source #

TraverseMsg Disembargo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Disembargo msgA -> m (Disembargo msgB) Source #

TraverseMsg Release Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Release msgA -> m (Release msgB) Source #

TraverseMsg Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Resolve msgA -> m (Resolve msgB) Source #

TraverseMsg Finish Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Finish msgA -> m (Finish msgB) Source #

TraverseMsg Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Return msgA -> m (Return msgB) Source #

TraverseMsg Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Call'sendResultsTo msgA -> m (Call'sendResultsTo msgB) Source #

TraverseMsg Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Call msgA -> m (Call msgB) Source #

TraverseMsg Bootstrap Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Bootstrap msgA -> m (Bootstrap msgB) Source #

TraverseMsg Message Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Message msgA -> m (Message msgB) Source #

TraverseMsg RealmGateway'export'params Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> RealmGateway'export'params msgA -> m (RealmGateway'export'params msgB) Source #

TraverseMsg RealmGateway'import'params Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> RealmGateway'import'params msgA -> m (RealmGateway'import'params msgB) Source #

TraverseMsg Persistent'SaveResults Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Persistent'SaveResults msgA -> m (Persistent'SaveResults msgB) Source #

TraverseMsg Persistent'SaveParams Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Persistent'SaveParams msgA -> m (Persistent'SaveParams msgB) Source #

TraverseMsg DiscriminatorOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> DiscriminatorOptions msgA -> m (DiscriminatorOptions msgB) Source #

TraverseMsg FlattenOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> FlattenOptions msgA -> m (FlattenOptions msgB) Source #

TraverseMsg Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Value'Call msgA -> m (Value'Call msgB) Source #

TraverseMsg Value'Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Value'Field msgA -> m (Value'Field msgB) Source #

TraverseMsg Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Value msgA -> m (Value msgB) Source #

Orphan instances

Thaw a => Thaw (Maybe a) Source # 
Instance details

Associated Types

type Mutable s (Maybe a) :: Type Source #

Methods

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

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

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

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