{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}
module Capnp.Capnp.Rpc where
import Data.Int
import Data.Word
import GHC.Generics (Generic)
import Data.Capnp.Bits (Word1)
import qualified Data.Bits
import qualified Data.Maybe
import qualified Data.Capnp.Classes as C'
import qualified Data.Capnp.Basics as B'
import qualified Data.Capnp.GenHelpers as H'
import qualified Data.Capnp.TraversalLimit as TL'
import qualified Data.Capnp.Untyped as U'
import qualified Data.Capnp.Message as M'
import qualified Capnp.ById.Xbdf87d7bb8304e81
newtype Accept msg = Accept_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Accept msg) where
fromStruct = pure . Accept_newtype_
instance C'.ToStruct msg (Accept msg) where
toStruct (Accept_newtype_ struct) = struct
instance C'.IsPtr msg (Accept msg) where
fromPtr msg ptr = Accept_newtype_ <$> C'.fromPtr msg ptr
toPtr (Accept_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Accept msg) where
newtype List msg (Accept msg) = List_Accept (U'.ListOf msg (U'.Struct msg))
length (List_Accept l) = U'.length l
index i (List_Accept l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Accept msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Accept (M'.MutMsg s)) where
setIndex (Accept_newtype_ elt) i (List_Accept l) = U'.setIndex elt i l
newList msg len = List_Accept <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (Accept msg) msg where
message (Accept_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Accept msg) msg where
messageDefault = Accept_newtype_ . U'.messageDefault
instance C'.Allocate s (Accept (M'.MutMsg s)) where
new msg = Accept_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (Accept msg)) where
fromPtr msg ptr = List_Accept <$> C'.fromPtr msg ptr
toPtr (List_Accept l) = C'.toPtr l
get_Accept'questionId :: U'.ReadCtx m msg => Accept msg -> m Word32
get_Accept'questionId (Accept_newtype_ struct) = H'.getWordField struct 0 0 0
has_Accept'questionId :: U'.ReadCtx m msg => Accept msg -> m Bool
has_Accept'questionId(Accept_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Accept'questionId :: U'.RWCtx m s => Accept (M'.MutMsg s) -> Word32 -> m ()
set_Accept'questionId (Accept_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Accept'provision :: U'.ReadCtx m msg => Accept msg -> m (Maybe (U'.Ptr msg))
get_Accept'provision (Accept_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_Accept'provision :: U'.ReadCtx m msg => Accept msg -> m Bool
has_Accept'provision(Accept_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_Accept'provision :: U'.RWCtx m s => Accept (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Accept'provision (Accept_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
get_Accept'embargo :: U'.ReadCtx m msg => Accept msg -> m Bool
get_Accept'embargo (Accept_newtype_ struct) = H'.getWordField struct 0 32 0
has_Accept'embargo :: U'.ReadCtx m msg => Accept msg -> m Bool
has_Accept'embargo(Accept_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Accept'embargo :: U'.RWCtx m s => Accept (M'.MutMsg s) -> Bool -> m ()
set_Accept'embargo (Accept_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word1) 0 32 0
newtype Bootstrap msg = Bootstrap_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Bootstrap msg) where
fromStruct = pure . Bootstrap_newtype_
instance C'.ToStruct msg (Bootstrap msg) where
toStruct (Bootstrap_newtype_ struct) = struct
instance C'.IsPtr msg (Bootstrap msg) where
fromPtr msg ptr = Bootstrap_newtype_ <$> C'.fromPtr msg ptr
toPtr (Bootstrap_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Bootstrap msg) where
newtype List msg (Bootstrap msg) = List_Bootstrap (U'.ListOf msg (U'.Struct msg))
length (List_Bootstrap l) = U'.length l
index i (List_Bootstrap l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Bootstrap msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Bootstrap (M'.MutMsg s)) where
setIndex (Bootstrap_newtype_ elt) i (List_Bootstrap l) = U'.setIndex elt i l
newList msg len = List_Bootstrap <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (Bootstrap msg) msg where
message (Bootstrap_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Bootstrap msg) msg where
messageDefault = Bootstrap_newtype_ . U'.messageDefault
instance C'.Allocate s (Bootstrap (M'.MutMsg s)) where
new msg = Bootstrap_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (Bootstrap msg)) where
fromPtr msg ptr = List_Bootstrap <$> C'.fromPtr msg ptr
toPtr (List_Bootstrap l) = C'.toPtr l
get_Bootstrap'questionId :: U'.ReadCtx m msg => Bootstrap msg -> m Word32
get_Bootstrap'questionId (Bootstrap_newtype_ struct) = H'.getWordField struct 0 0 0
has_Bootstrap'questionId :: U'.ReadCtx m msg => Bootstrap msg -> m Bool
has_Bootstrap'questionId(Bootstrap_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Bootstrap'questionId :: U'.RWCtx m s => Bootstrap (M'.MutMsg s) -> Word32 -> m ()
set_Bootstrap'questionId (Bootstrap_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Bootstrap'deprecatedObjectId :: U'.ReadCtx m msg => Bootstrap msg -> m (Maybe (U'.Ptr msg))
get_Bootstrap'deprecatedObjectId (Bootstrap_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_Bootstrap'deprecatedObjectId :: U'.ReadCtx m msg => Bootstrap msg -> m Bool
has_Bootstrap'deprecatedObjectId(Bootstrap_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_Bootstrap'deprecatedObjectId :: U'.RWCtx m s => Bootstrap (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Bootstrap'deprecatedObjectId (Bootstrap_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
newtype Call msg = Call_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Call msg) where
fromStruct = pure . Call_newtype_
instance C'.ToStruct msg (Call msg) where
toStruct (Call_newtype_ struct) = struct
instance C'.IsPtr msg (Call msg) where
fromPtr msg ptr = Call_newtype_ <$> C'.fromPtr msg ptr
toPtr (Call_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Call msg) where
newtype List msg (Call msg) = List_Call (U'.ListOf msg (U'.Struct msg))
length (List_Call l) = U'.length l
index i (List_Call l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Call msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Call (M'.MutMsg s)) where
setIndex (Call_newtype_ elt) i (List_Call l) = U'.setIndex elt i l
newList msg len = List_Call <$> U'.allocCompositeList msg 3 3 len
instance U'.HasMessage (Call msg) msg where
message (Call_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Call msg) msg where
messageDefault = Call_newtype_ . U'.messageDefault
instance C'.Allocate s (Call (M'.MutMsg s)) where
new msg = Call_newtype_ <$> U'.allocStruct msg 3 3
instance C'.IsPtr msg (B'.List msg (Call msg)) where
fromPtr msg ptr = List_Call <$> C'.fromPtr msg ptr
toPtr (List_Call l) = C'.toPtr l
get_Call'questionId :: U'.ReadCtx m msg => Call msg -> m Word32
get_Call'questionId (Call_newtype_ struct) = H'.getWordField struct 0 0 0
has_Call'questionId :: U'.ReadCtx m msg => Call msg -> m Bool
has_Call'questionId(Call_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Call'questionId :: U'.RWCtx m s => Call (M'.MutMsg s) -> Word32 -> m ()
set_Call'questionId (Call_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Call'target :: U'.ReadCtx m msg => Call msg -> m (MessageTarget msg)
get_Call'target (Call_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_Call'target :: U'.ReadCtx m msg => Call msg -> m Bool
has_Call'target(Call_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_Call'target :: U'.RWCtx m s => Call (M'.MutMsg s) -> (MessageTarget (M'.MutMsg s)) -> m ()
set_Call'target (Call_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
new_Call'target :: U'.RWCtx m s => Call (M'.MutMsg s) -> m ((MessageTarget (M'.MutMsg s)))
new_Call'target struct = do
result <- C'.new (U'.message struct)
set_Call'target struct result
pure result
get_Call'interfaceId :: U'.ReadCtx m msg => Call msg -> m Word64
get_Call'interfaceId (Call_newtype_ struct) = H'.getWordField struct 1 0 0
has_Call'interfaceId :: U'.ReadCtx m msg => Call msg -> m Bool
has_Call'interfaceId(Call_newtype_ struct) = pure $ 1 < U'.length (U'.dataSection struct)
set_Call'interfaceId :: U'.RWCtx m s => Call (M'.MutMsg s) -> Word64 -> m ()
set_Call'interfaceId (Call_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word64) 1 0 0
get_Call'methodId :: U'.ReadCtx m msg => Call msg -> m Word16
get_Call'methodId (Call_newtype_ struct) = H'.getWordField struct 0 32 0
has_Call'methodId :: U'.ReadCtx m msg => Call msg -> m Bool
has_Call'methodId(Call_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Call'methodId :: U'.RWCtx m s => Call (M'.MutMsg s) -> Word16 -> m ()
set_Call'methodId (Call_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word16) 0 32 0
get_Call'params :: U'.ReadCtx m msg => Call msg -> m (Payload msg)
get_Call'params (Call_newtype_ struct) =
U'.getPtr 1 struct
>>= C'.fromPtr (U'.message struct)
has_Call'params :: U'.ReadCtx m msg => Call msg -> m Bool
has_Call'params(Call_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 1 struct
set_Call'params :: U'.RWCtx m s => Call (M'.MutMsg s) -> (Payload (M'.MutMsg s)) -> m ()
set_Call'params (Call_newtype_ struct) value = U'.setPtr (C'.toPtr value) 1 struct
new_Call'params :: U'.RWCtx m s => Call (M'.MutMsg s) -> m ((Payload (M'.MutMsg s)))
new_Call'params struct = do
result <- C'.new (U'.message struct)
set_Call'params struct result
pure result
get_Call'sendResultsTo :: U'.ReadCtx m msg => Call msg -> m (Call'sendResultsTo msg)
get_Call'sendResultsTo (Call_newtype_ struct) = C'.fromStruct struct
has_Call'sendResultsTo :: U'.ReadCtx m msg => Call msg -> m Bool
has_Call'sendResultsTo(Call_newtype_ struct) = pure True
get_Call'allowThirdPartyTailCall :: U'.ReadCtx m msg => Call msg -> m Bool
get_Call'allowThirdPartyTailCall (Call_newtype_ struct) = H'.getWordField struct 2 0 0
has_Call'allowThirdPartyTailCall :: U'.ReadCtx m msg => Call msg -> m Bool
has_Call'allowThirdPartyTailCall(Call_newtype_ struct) = pure $ 2 < U'.length (U'.dataSection struct)
set_Call'allowThirdPartyTailCall :: U'.RWCtx m s => Call (M'.MutMsg s) -> Bool -> m ()
set_Call'allowThirdPartyTailCall (Call_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word1) 2 0 0
newtype CapDescriptor msg = CapDescriptor_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (CapDescriptor msg) where
fromStruct = pure . CapDescriptor_newtype_
instance C'.ToStruct msg (CapDescriptor msg) where
toStruct (CapDescriptor_newtype_ struct) = struct
instance C'.IsPtr msg (CapDescriptor msg) where
fromPtr msg ptr = CapDescriptor_newtype_ <$> C'.fromPtr msg ptr
toPtr (CapDescriptor_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (CapDescriptor msg) where
newtype List msg (CapDescriptor msg) = List_CapDescriptor (U'.ListOf msg (U'.Struct msg))
length (List_CapDescriptor l) = U'.length l
index i (List_CapDescriptor l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (CapDescriptor msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (CapDescriptor (M'.MutMsg s)) where
setIndex (CapDescriptor_newtype_ elt) i (List_CapDescriptor l) = U'.setIndex elt i l
newList msg len = List_CapDescriptor <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (CapDescriptor msg) msg where
message (CapDescriptor_newtype_ struct) = U'.message struct
instance U'.MessageDefault (CapDescriptor msg) msg where
messageDefault = CapDescriptor_newtype_ . U'.messageDefault
instance C'.Allocate s (CapDescriptor (M'.MutMsg s)) where
new msg = CapDescriptor_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (CapDescriptor msg)) where
fromPtr msg ptr = List_CapDescriptor <$> C'.fromPtr msg ptr
toPtr (List_CapDescriptor l) = C'.toPtr l
data CapDescriptor' msg =
CapDescriptor'none |
CapDescriptor'senderHosted Word32 |
CapDescriptor'senderPromise Word32 |
CapDescriptor'receiverHosted Word32 |
CapDescriptor'receiverAnswer (PromisedAnswer msg) |
CapDescriptor'thirdPartyHosted (ThirdPartyCapDescriptor msg) |
CapDescriptor'unknown' Word16
get_CapDescriptor' :: U'.ReadCtx m msg => CapDescriptor msg -> m (CapDescriptor' msg)
get_CapDescriptor' (CapDescriptor_newtype_ struct) = C'.fromStruct struct
has_CapDescriptor' :: U'.ReadCtx m msg => CapDescriptor msg -> m Bool
has_CapDescriptor'(CapDescriptor_newtype_ struct) = pure True
set_CapDescriptor'none :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> m ()
set_CapDescriptor'none (CapDescriptor_newtype_ struct) = H'.setWordField struct (0 :: Word16) 0 0 0
set_CapDescriptor'senderHosted :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> Word32 -> m ()
set_CapDescriptor'senderHosted (CapDescriptor_newtype_ struct) value = do
H'.setWordField struct (1 :: Word16) 0 0 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 32 0
set_CapDescriptor'senderPromise :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> Word32 -> m ()
set_CapDescriptor'senderPromise (CapDescriptor_newtype_ struct) value = do
H'.setWordField struct (2 :: Word16) 0 0 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 32 0
set_CapDescriptor'receiverHosted :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> Word32 -> m ()
set_CapDescriptor'receiverHosted (CapDescriptor_newtype_ struct) value = do
H'.setWordField struct (3 :: Word16) 0 0 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 32 0
set_CapDescriptor'receiverAnswer :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> (PromisedAnswer (M'.MutMsg s)) -> m ()
set_CapDescriptor'receiverAnswer(CapDescriptor_newtype_ struct) value = do
H'.setWordField struct (4 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_CapDescriptor'receiverAnswer :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> m ((PromisedAnswer (M'.MutMsg s)))
new_CapDescriptor'receiverAnswer struct = do
result <- C'.new (U'.message struct)
set_CapDescriptor'receiverAnswer struct result
pure result
set_CapDescriptor'thirdPartyHosted :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> (ThirdPartyCapDescriptor (M'.MutMsg s)) -> m ()
set_CapDescriptor'thirdPartyHosted(CapDescriptor_newtype_ struct) value = do
H'.setWordField struct (5 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_CapDescriptor'thirdPartyHosted :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> m ((ThirdPartyCapDescriptor (M'.MutMsg s)))
new_CapDescriptor'thirdPartyHosted struct = do
result <- C'.new (U'.message struct)
set_CapDescriptor'thirdPartyHosted struct result
pure result
set_CapDescriptor'unknown' :: U'.RWCtx m s => CapDescriptor (M'.MutMsg s) -> Word16 -> m ()
set_CapDescriptor'unknown'(CapDescriptor_newtype_ struct) tagValue = H'.setWordField struct (tagValue :: Word16) 0 0 0
instance C'.FromStruct msg (CapDescriptor' msg) where
fromStruct struct = do
tag <- H'.getWordField struct 0 0 0
case tag of
5 -> CapDescriptor'thirdPartyHosted <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
4 -> CapDescriptor'receiverAnswer <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
3 -> CapDescriptor'receiverHosted <$> H'.getWordField struct 0 32 0
2 -> CapDescriptor'senderPromise <$> H'.getWordField struct 0 32 0
1 -> CapDescriptor'senderHosted <$> H'.getWordField struct 0 32 0
0 -> pure CapDescriptor'none
_ -> pure $ CapDescriptor'unknown' tag
newtype Disembargo msg = Disembargo_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Disembargo msg) where
fromStruct = pure . Disembargo_newtype_
instance C'.ToStruct msg (Disembargo msg) where
toStruct (Disembargo_newtype_ struct) = struct
instance C'.IsPtr msg (Disembargo msg) where
fromPtr msg ptr = Disembargo_newtype_ <$> C'.fromPtr msg ptr
toPtr (Disembargo_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Disembargo msg) where
newtype List msg (Disembargo msg) = List_Disembargo (U'.ListOf msg (U'.Struct msg))
length (List_Disembargo l) = U'.length l
index i (List_Disembargo l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Disembargo msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Disembargo (M'.MutMsg s)) where
setIndex (Disembargo_newtype_ elt) i (List_Disembargo l) = U'.setIndex elt i l
newList msg len = List_Disembargo <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (Disembargo msg) msg where
message (Disembargo_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Disembargo msg) msg where
messageDefault = Disembargo_newtype_ . U'.messageDefault
instance C'.Allocate s (Disembargo (M'.MutMsg s)) where
new msg = Disembargo_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (Disembargo msg)) where
fromPtr msg ptr = List_Disembargo <$> C'.fromPtr msg ptr
toPtr (List_Disembargo l) = C'.toPtr l
get_Disembargo'target :: U'.ReadCtx m msg => Disembargo msg -> m (MessageTarget msg)
get_Disembargo'target (Disembargo_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_Disembargo'target :: U'.ReadCtx m msg => Disembargo msg -> m Bool
has_Disembargo'target(Disembargo_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_Disembargo'target :: U'.RWCtx m s => Disembargo (M'.MutMsg s) -> (MessageTarget (M'.MutMsg s)) -> m ()
set_Disembargo'target (Disembargo_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
new_Disembargo'target :: U'.RWCtx m s => Disembargo (M'.MutMsg s) -> m ((MessageTarget (M'.MutMsg s)))
new_Disembargo'target struct = do
result <- C'.new (U'.message struct)
set_Disembargo'target struct result
pure result
get_Disembargo'context :: U'.ReadCtx m msg => Disembargo msg -> m (Disembargo'context msg)
get_Disembargo'context (Disembargo_newtype_ struct) = C'.fromStruct struct
has_Disembargo'context :: U'.ReadCtx m msg => Disembargo msg -> m Bool
has_Disembargo'context(Disembargo_newtype_ struct) = pure True
newtype Exception msg = Exception_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Exception msg) where
fromStruct = pure . Exception_newtype_
instance C'.ToStruct msg (Exception msg) where
toStruct (Exception_newtype_ struct) = struct
instance C'.IsPtr msg (Exception msg) where
fromPtr msg ptr = Exception_newtype_ <$> C'.fromPtr msg ptr
toPtr (Exception_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Exception msg) where
newtype List msg (Exception msg) = List_Exception (U'.ListOf msg (U'.Struct msg))
length (List_Exception l) = U'.length l
index i (List_Exception l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Exception msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Exception (M'.MutMsg s)) where
setIndex (Exception_newtype_ elt) i (List_Exception l) = U'.setIndex elt i l
newList msg len = List_Exception <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (Exception msg) msg where
message (Exception_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Exception msg) msg where
messageDefault = Exception_newtype_ . U'.messageDefault
instance C'.Allocate s (Exception (M'.MutMsg s)) where
new msg = Exception_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (Exception msg)) where
fromPtr msg ptr = List_Exception <$> C'.fromPtr msg ptr
toPtr (List_Exception l) = C'.toPtr l
get_Exception'reason :: U'.ReadCtx m msg => Exception msg -> m (B'.Text msg)
get_Exception'reason (Exception_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_Exception'reason :: U'.ReadCtx m msg => Exception msg -> m Bool
has_Exception'reason(Exception_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_Exception'reason :: U'.RWCtx m s => Exception (M'.MutMsg s) -> (B'.Text (M'.MutMsg s)) -> m ()
set_Exception'reason (Exception_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
new_Exception'reason :: U'.RWCtx m s => Int -> Exception (M'.MutMsg s) -> m ((B'.Text (M'.MutMsg s)))
new_Exception'reason len struct = do
result <- B'.newText (U'.message struct) len
set_Exception'reason struct result
pure result
get_Exception'obsoleteIsCallersFault :: U'.ReadCtx m msg => Exception msg -> m Bool
get_Exception'obsoleteIsCallersFault (Exception_newtype_ struct) = H'.getWordField struct 0 0 0
has_Exception'obsoleteIsCallersFault :: U'.ReadCtx m msg => Exception msg -> m Bool
has_Exception'obsoleteIsCallersFault(Exception_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Exception'obsoleteIsCallersFault :: U'.RWCtx m s => Exception (M'.MutMsg s) -> Bool -> m ()
set_Exception'obsoleteIsCallersFault (Exception_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word1) 0 0 0
get_Exception'obsoleteDurability :: U'.ReadCtx m msg => Exception msg -> m Word16
get_Exception'obsoleteDurability (Exception_newtype_ struct) = H'.getWordField struct 0 16 0
has_Exception'obsoleteDurability :: U'.ReadCtx m msg => Exception msg -> m Bool
has_Exception'obsoleteDurability(Exception_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Exception'obsoleteDurability :: U'.RWCtx m s => Exception (M'.MutMsg s) -> Word16 -> m ()
set_Exception'obsoleteDurability (Exception_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word16) 0 16 0
get_Exception'type_ :: U'.ReadCtx m msg => Exception msg -> m Exception'Type
get_Exception'type_ (Exception_newtype_ struct) = H'.getWordField struct 0 32 0
has_Exception'type_ :: U'.ReadCtx m msg => Exception msg -> m Bool
has_Exception'type_(Exception_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Exception'type_ :: U'.RWCtx m s => Exception (M'.MutMsg s) -> Exception'Type -> m ()
set_Exception'type_ (Exception_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word16) 0 32 0
newtype Finish msg = Finish_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Finish msg) where
fromStruct = pure . Finish_newtype_
instance C'.ToStruct msg (Finish msg) where
toStruct (Finish_newtype_ struct) = struct
instance C'.IsPtr msg (Finish msg) where
fromPtr msg ptr = Finish_newtype_ <$> C'.fromPtr msg ptr
toPtr (Finish_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Finish msg) where
newtype List msg (Finish msg) = List_Finish (U'.ListOf msg (U'.Struct msg))
length (List_Finish l) = U'.length l
index i (List_Finish l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Finish msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Finish (M'.MutMsg s)) where
setIndex (Finish_newtype_ elt) i (List_Finish l) = U'.setIndex elt i l
newList msg len = List_Finish <$> U'.allocCompositeList msg 1 0 len
instance U'.HasMessage (Finish msg) msg where
message (Finish_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Finish msg) msg where
messageDefault = Finish_newtype_ . U'.messageDefault
instance C'.Allocate s (Finish (M'.MutMsg s)) where
new msg = Finish_newtype_ <$> U'.allocStruct msg 1 0
instance C'.IsPtr msg (B'.List msg (Finish msg)) where
fromPtr msg ptr = List_Finish <$> C'.fromPtr msg ptr
toPtr (List_Finish l) = C'.toPtr l
get_Finish'questionId :: U'.ReadCtx m msg => Finish msg -> m Word32
get_Finish'questionId (Finish_newtype_ struct) = H'.getWordField struct 0 0 0
has_Finish'questionId :: U'.ReadCtx m msg => Finish msg -> m Bool
has_Finish'questionId(Finish_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Finish'questionId :: U'.RWCtx m s => Finish (M'.MutMsg s) -> Word32 -> m ()
set_Finish'questionId (Finish_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Finish'releaseResultCaps :: U'.ReadCtx m msg => Finish msg -> m Bool
get_Finish'releaseResultCaps (Finish_newtype_ struct) = H'.getWordField struct 0 32 1
has_Finish'releaseResultCaps :: U'.ReadCtx m msg => Finish msg -> m Bool
has_Finish'releaseResultCaps(Finish_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Finish'releaseResultCaps :: U'.RWCtx m s => Finish (M'.MutMsg s) -> Bool -> m ()
set_Finish'releaseResultCaps (Finish_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word1) 0 32 1
newtype Join msg = Join_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Join msg) where
fromStruct = pure . Join_newtype_
instance C'.ToStruct msg (Join msg) where
toStruct (Join_newtype_ struct) = struct
instance C'.IsPtr msg (Join msg) where
fromPtr msg ptr = Join_newtype_ <$> C'.fromPtr msg ptr
toPtr (Join_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Join msg) where
newtype List msg (Join msg) = List_Join (U'.ListOf msg (U'.Struct msg))
length (List_Join l) = U'.length l
index i (List_Join l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Join msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Join (M'.MutMsg s)) where
setIndex (Join_newtype_ elt) i (List_Join l) = U'.setIndex elt i l
newList msg len = List_Join <$> U'.allocCompositeList msg 1 2 len
instance U'.HasMessage (Join msg) msg where
message (Join_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Join msg) msg where
messageDefault = Join_newtype_ . U'.messageDefault
instance C'.Allocate s (Join (M'.MutMsg s)) where
new msg = Join_newtype_ <$> U'.allocStruct msg 1 2
instance C'.IsPtr msg (B'.List msg (Join msg)) where
fromPtr msg ptr = List_Join <$> C'.fromPtr msg ptr
toPtr (List_Join l) = C'.toPtr l
get_Join'questionId :: U'.ReadCtx m msg => Join msg -> m Word32
get_Join'questionId (Join_newtype_ struct) = H'.getWordField struct 0 0 0
has_Join'questionId :: U'.ReadCtx m msg => Join msg -> m Bool
has_Join'questionId(Join_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Join'questionId :: U'.RWCtx m s => Join (M'.MutMsg s) -> Word32 -> m ()
set_Join'questionId (Join_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Join'target :: U'.ReadCtx m msg => Join msg -> m (MessageTarget msg)
get_Join'target (Join_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_Join'target :: U'.ReadCtx m msg => Join msg -> m Bool
has_Join'target(Join_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_Join'target :: U'.RWCtx m s => Join (M'.MutMsg s) -> (MessageTarget (M'.MutMsg s)) -> m ()
set_Join'target (Join_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
new_Join'target :: U'.RWCtx m s => Join (M'.MutMsg s) -> m ((MessageTarget (M'.MutMsg s)))
new_Join'target struct = do
result <- C'.new (U'.message struct)
set_Join'target struct result
pure result
get_Join'keyPart :: U'.ReadCtx m msg => Join msg -> m (Maybe (U'.Ptr msg))
get_Join'keyPart (Join_newtype_ struct) =
U'.getPtr 1 struct
>>= C'.fromPtr (U'.message struct)
has_Join'keyPart :: U'.ReadCtx m msg => Join msg -> m Bool
has_Join'keyPart(Join_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 1 struct
set_Join'keyPart :: U'.RWCtx m s => Join (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Join'keyPart (Join_newtype_ struct) value = U'.setPtr (C'.toPtr value) 1 struct
newtype Message msg = Message_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Message msg) where
fromStruct = pure . Message_newtype_
instance C'.ToStruct msg (Message msg) where
toStruct (Message_newtype_ struct) = struct
instance C'.IsPtr msg (Message msg) where
fromPtr msg ptr = Message_newtype_ <$> C'.fromPtr msg ptr
toPtr (Message_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Message msg) where
newtype List msg (Message msg) = List_Message (U'.ListOf msg (U'.Struct msg))
length (List_Message l) = U'.length l
index i (List_Message l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Message msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Message (M'.MutMsg s)) where
setIndex (Message_newtype_ elt) i (List_Message l) = U'.setIndex elt i l
newList msg len = List_Message <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (Message msg) msg where
message (Message_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Message msg) msg where
messageDefault = Message_newtype_ . U'.messageDefault
instance C'.Allocate s (Message (M'.MutMsg s)) where
new msg = Message_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (Message msg)) where
fromPtr msg ptr = List_Message <$> C'.fromPtr msg ptr
toPtr (List_Message l) = C'.toPtr l
data Message' msg =
Message'unimplemented (Message msg) |
Message'abort (Exception msg) |
Message'call (Call msg) |
Message'return (Return msg) |
Message'finish (Finish msg) |
Message'resolve (Resolve msg) |
Message'release (Release msg) |
Message'obsoleteSave (Maybe (U'.Ptr msg)) |
Message'bootstrap (Bootstrap msg) |
Message'obsoleteDelete (Maybe (U'.Ptr msg)) |
Message'provide (Provide msg) |
Message'accept (Accept msg) |
Message'join (Join msg) |
Message'disembargo (Disembargo msg) |
Message'unknown' Word16
get_Message' :: U'.ReadCtx m msg => Message msg -> m (Message' msg)
get_Message' (Message_newtype_ struct) = C'.fromStruct struct
has_Message' :: U'.ReadCtx m msg => Message msg -> m Bool
has_Message'(Message_newtype_ struct) = pure True
set_Message'unimplemented :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Message (M'.MutMsg s)) -> m ()
set_Message'unimplemented(Message_newtype_ struct) value = do
H'.setWordField struct (0 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'unimplemented :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Message (M'.MutMsg s)))
new_Message'unimplemented struct = do
result <- C'.new (U'.message struct)
set_Message'unimplemented struct result
pure result
set_Message'abort :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Exception (M'.MutMsg s)) -> m ()
set_Message'abort(Message_newtype_ struct) value = do
H'.setWordField struct (1 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'abort :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Exception (M'.MutMsg s)))
new_Message'abort struct = do
result <- C'.new (U'.message struct)
set_Message'abort struct result
pure result
set_Message'call :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Call (M'.MutMsg s)) -> m ()
set_Message'call(Message_newtype_ struct) value = do
H'.setWordField struct (2 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'call :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Call (M'.MutMsg s)))
new_Message'call struct = do
result <- C'.new (U'.message struct)
set_Message'call struct result
pure result
set_Message'return :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Return (M'.MutMsg s)) -> m ()
set_Message'return(Message_newtype_ struct) value = do
H'.setWordField struct (3 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'return :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Return (M'.MutMsg s)))
new_Message'return struct = do
result <- C'.new (U'.message struct)
set_Message'return struct result
pure result
set_Message'finish :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Finish (M'.MutMsg s)) -> m ()
set_Message'finish(Message_newtype_ struct) value = do
H'.setWordField struct (4 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'finish :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Finish (M'.MutMsg s)))
new_Message'finish struct = do
result <- C'.new (U'.message struct)
set_Message'finish struct result
pure result
set_Message'resolve :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Resolve (M'.MutMsg s)) -> m ()
set_Message'resolve(Message_newtype_ struct) value = do
H'.setWordField struct (5 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'resolve :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Resolve (M'.MutMsg s)))
new_Message'resolve struct = do
result <- C'.new (U'.message struct)
set_Message'resolve struct result
pure result
set_Message'release :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Release (M'.MutMsg s)) -> m ()
set_Message'release(Message_newtype_ struct) value = do
H'.setWordField struct (6 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'release :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Release (M'.MutMsg s)))
new_Message'release struct = do
result <- C'.new (U'.message struct)
set_Message'release struct result
pure result
set_Message'obsoleteSave :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Message'obsoleteSave(Message_newtype_ struct) value = do
H'.setWordField struct (7 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
set_Message'bootstrap :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Bootstrap (M'.MutMsg s)) -> m ()
set_Message'bootstrap(Message_newtype_ struct) value = do
H'.setWordField struct (8 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'bootstrap :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Bootstrap (M'.MutMsg s)))
new_Message'bootstrap struct = do
result <- C'.new (U'.message struct)
set_Message'bootstrap struct result
pure result
set_Message'obsoleteDelete :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Message'obsoleteDelete(Message_newtype_ struct) value = do
H'.setWordField struct (9 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
set_Message'provide :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Provide (M'.MutMsg s)) -> m ()
set_Message'provide(Message_newtype_ struct) value = do
H'.setWordField struct (10 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'provide :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Provide (M'.MutMsg s)))
new_Message'provide struct = do
result <- C'.new (U'.message struct)
set_Message'provide struct result
pure result
set_Message'accept :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Accept (M'.MutMsg s)) -> m ()
set_Message'accept(Message_newtype_ struct) value = do
H'.setWordField struct (11 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'accept :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Accept (M'.MutMsg s)))
new_Message'accept struct = do
result <- C'.new (U'.message struct)
set_Message'accept struct result
pure result
set_Message'join :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Join (M'.MutMsg s)) -> m ()
set_Message'join(Message_newtype_ struct) value = do
H'.setWordField struct (12 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'join :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Join (M'.MutMsg s)))
new_Message'join struct = do
result <- C'.new (U'.message struct)
set_Message'join struct result
pure result
set_Message'disembargo :: U'.RWCtx m s => Message (M'.MutMsg s) -> (Disembargo (M'.MutMsg s)) -> m ()
set_Message'disembargo(Message_newtype_ struct) value = do
H'.setWordField struct (13 :: Word16) 0 0 0
U'.setPtr (C'.toPtr value) 0 struct
new_Message'disembargo :: U'.RWCtx m s => Message (M'.MutMsg s) -> m ((Disembargo (M'.MutMsg s)))
new_Message'disembargo struct = do
result <- C'.new (U'.message struct)
set_Message'disembargo struct result
pure result
set_Message'unknown' :: U'.RWCtx m s => Message (M'.MutMsg s) -> Word16 -> m ()
set_Message'unknown'(Message_newtype_ struct) tagValue = H'.setWordField struct (tagValue :: Word16) 0 0 0
instance C'.FromStruct msg (Message' msg) where
fromStruct struct = do
tag <- H'.getWordField struct 0 0 0
case tag of
13 -> Message'disembargo <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
12 -> Message'join <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
11 -> Message'accept <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
10 -> Message'provide <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
9 -> Message'obsoleteDelete <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
8 -> Message'bootstrap <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
7 -> Message'obsoleteSave <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
6 -> Message'release <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
5 -> Message'resolve <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
4 -> Message'finish <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
3 -> Message'return <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
2 -> Message'call <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
1 -> Message'abort <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
0 -> Message'unimplemented <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
_ -> pure $ Message'unknown' tag
newtype MessageTarget msg = MessageTarget_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (MessageTarget msg) where
fromStruct = pure . MessageTarget_newtype_
instance C'.ToStruct msg (MessageTarget msg) where
toStruct (MessageTarget_newtype_ struct) = struct
instance C'.IsPtr msg (MessageTarget msg) where
fromPtr msg ptr = MessageTarget_newtype_ <$> C'.fromPtr msg ptr
toPtr (MessageTarget_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (MessageTarget msg) where
newtype List msg (MessageTarget msg) = List_MessageTarget (U'.ListOf msg (U'.Struct msg))
length (List_MessageTarget l) = U'.length l
index i (List_MessageTarget l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (MessageTarget msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (MessageTarget (M'.MutMsg s)) where
setIndex (MessageTarget_newtype_ elt) i (List_MessageTarget l) = U'.setIndex elt i l
newList msg len = List_MessageTarget <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (MessageTarget msg) msg where
message (MessageTarget_newtype_ struct) = U'.message struct
instance U'.MessageDefault (MessageTarget msg) msg where
messageDefault = MessageTarget_newtype_ . U'.messageDefault
instance C'.Allocate s (MessageTarget (M'.MutMsg s)) where
new msg = MessageTarget_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (MessageTarget msg)) where
fromPtr msg ptr = List_MessageTarget <$> C'.fromPtr msg ptr
toPtr (List_MessageTarget l) = C'.toPtr l
data MessageTarget' msg =
MessageTarget'importedCap Word32 |
MessageTarget'promisedAnswer (PromisedAnswer msg) |
MessageTarget'unknown' Word16
get_MessageTarget' :: U'.ReadCtx m msg => MessageTarget msg -> m (MessageTarget' msg)
get_MessageTarget' (MessageTarget_newtype_ struct) = C'.fromStruct struct
has_MessageTarget' :: U'.ReadCtx m msg => MessageTarget msg -> m Bool
has_MessageTarget'(MessageTarget_newtype_ struct) = pure True
set_MessageTarget'importedCap :: U'.RWCtx m s => MessageTarget (M'.MutMsg s) -> Word32 -> m ()
set_MessageTarget'importedCap (MessageTarget_newtype_ struct) value = do
H'.setWordField struct (0 :: Word16) 0 32 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
set_MessageTarget'promisedAnswer :: U'.RWCtx m s => MessageTarget (M'.MutMsg s) -> (PromisedAnswer (M'.MutMsg s)) -> m ()
set_MessageTarget'promisedAnswer(MessageTarget_newtype_ struct) value = do
H'.setWordField struct (1 :: Word16) 0 32 0
U'.setPtr (C'.toPtr value) 0 struct
new_MessageTarget'promisedAnswer :: U'.RWCtx m s => MessageTarget (M'.MutMsg s) -> m ((PromisedAnswer (M'.MutMsg s)))
new_MessageTarget'promisedAnswer struct = do
result <- C'.new (U'.message struct)
set_MessageTarget'promisedAnswer struct result
pure result
set_MessageTarget'unknown' :: U'.RWCtx m s => MessageTarget (M'.MutMsg s) -> Word16 -> m ()
set_MessageTarget'unknown'(MessageTarget_newtype_ struct) tagValue = H'.setWordField struct (tagValue :: Word16) 0 32 0
instance C'.FromStruct msg (MessageTarget' msg) where
fromStruct struct = do
tag <- H'.getWordField struct 0 32 0
case tag of
1 -> MessageTarget'promisedAnswer <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
0 -> MessageTarget'importedCap <$> H'.getWordField struct 0 0 0
_ -> pure $ MessageTarget'unknown' tag
newtype Payload msg = Payload_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Payload msg) where
fromStruct = pure . Payload_newtype_
instance C'.ToStruct msg (Payload msg) where
toStruct (Payload_newtype_ struct) = struct
instance C'.IsPtr msg (Payload msg) where
fromPtr msg ptr = Payload_newtype_ <$> C'.fromPtr msg ptr
toPtr (Payload_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Payload msg) where
newtype List msg (Payload msg) = List_Payload (U'.ListOf msg (U'.Struct msg))
length (List_Payload l) = U'.length l
index i (List_Payload l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Payload msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Payload (M'.MutMsg s)) where
setIndex (Payload_newtype_ elt) i (List_Payload l) = U'.setIndex elt i l
newList msg len = List_Payload <$> U'.allocCompositeList msg 0 2 len
instance U'.HasMessage (Payload msg) msg where
message (Payload_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Payload msg) msg where
messageDefault = Payload_newtype_ . U'.messageDefault
instance C'.Allocate s (Payload (M'.MutMsg s)) where
new msg = Payload_newtype_ <$> U'.allocStruct msg 0 2
instance C'.IsPtr msg (B'.List msg (Payload msg)) where
fromPtr msg ptr = List_Payload <$> C'.fromPtr msg ptr
toPtr (List_Payload l) = C'.toPtr l
get_Payload'content :: U'.ReadCtx m msg => Payload msg -> m (Maybe (U'.Ptr msg))
get_Payload'content (Payload_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_Payload'content :: U'.ReadCtx m msg => Payload msg -> m Bool
has_Payload'content(Payload_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_Payload'content :: U'.RWCtx m s => Payload (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Payload'content (Payload_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
get_Payload'capTable :: U'.ReadCtx m msg => Payload msg -> m (B'.List msg (CapDescriptor msg))
get_Payload'capTable (Payload_newtype_ struct) =
U'.getPtr 1 struct
>>= C'.fromPtr (U'.message struct)
has_Payload'capTable :: U'.ReadCtx m msg => Payload msg -> m Bool
has_Payload'capTable(Payload_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 1 struct
set_Payload'capTable :: U'.RWCtx m s => Payload (M'.MutMsg s) -> (B'.List (M'.MutMsg s) (CapDescriptor (M'.MutMsg s))) -> m ()
set_Payload'capTable (Payload_newtype_ struct) value = U'.setPtr (C'.toPtr value) 1 struct
new_Payload'capTable :: U'.RWCtx m s => Int -> Payload (M'.MutMsg s) -> m ((B'.List (M'.MutMsg s) (CapDescriptor (M'.MutMsg s))))
new_Payload'capTable len struct = do
result <- C'.newList (U'.message struct) len
set_Payload'capTable struct result
pure result
newtype PromisedAnswer msg = PromisedAnswer_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (PromisedAnswer msg) where
fromStruct = pure . PromisedAnswer_newtype_
instance C'.ToStruct msg (PromisedAnswer msg) where
toStruct (PromisedAnswer_newtype_ struct) = struct
instance C'.IsPtr msg (PromisedAnswer msg) where
fromPtr msg ptr = PromisedAnswer_newtype_ <$> C'.fromPtr msg ptr
toPtr (PromisedAnswer_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (PromisedAnswer msg) where
newtype List msg (PromisedAnswer msg) = List_PromisedAnswer (U'.ListOf msg (U'.Struct msg))
length (List_PromisedAnswer l) = U'.length l
index i (List_PromisedAnswer l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (PromisedAnswer msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (PromisedAnswer (M'.MutMsg s)) where
setIndex (PromisedAnswer_newtype_ elt) i (List_PromisedAnswer l) = U'.setIndex elt i l
newList msg len = List_PromisedAnswer <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (PromisedAnswer msg) msg where
message (PromisedAnswer_newtype_ struct) = U'.message struct
instance U'.MessageDefault (PromisedAnswer msg) msg where
messageDefault = PromisedAnswer_newtype_ . U'.messageDefault
instance C'.Allocate s (PromisedAnswer (M'.MutMsg s)) where
new msg = PromisedAnswer_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (PromisedAnswer msg)) where
fromPtr msg ptr = List_PromisedAnswer <$> C'.fromPtr msg ptr
toPtr (List_PromisedAnswer l) = C'.toPtr l
get_PromisedAnswer'questionId :: U'.ReadCtx m msg => PromisedAnswer msg -> m Word32
get_PromisedAnswer'questionId (PromisedAnswer_newtype_ struct) = H'.getWordField struct 0 0 0
has_PromisedAnswer'questionId :: U'.ReadCtx m msg => PromisedAnswer msg -> m Bool
has_PromisedAnswer'questionId(PromisedAnswer_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_PromisedAnswer'questionId :: U'.RWCtx m s => PromisedAnswer (M'.MutMsg s) -> Word32 -> m ()
set_PromisedAnswer'questionId (PromisedAnswer_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_PromisedAnswer'transform :: U'.ReadCtx m msg => PromisedAnswer msg -> m (B'.List msg (PromisedAnswer'Op msg))
get_PromisedAnswer'transform (PromisedAnswer_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_PromisedAnswer'transform :: U'.ReadCtx m msg => PromisedAnswer msg -> m Bool
has_PromisedAnswer'transform(PromisedAnswer_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_PromisedAnswer'transform :: U'.RWCtx m s => PromisedAnswer (M'.MutMsg s) -> (B'.List (M'.MutMsg s) (PromisedAnswer'Op (M'.MutMsg s))) -> m ()
set_PromisedAnswer'transform (PromisedAnswer_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
new_PromisedAnswer'transform :: U'.RWCtx m s => Int -> PromisedAnswer (M'.MutMsg s) -> m ((B'.List (M'.MutMsg s) (PromisedAnswer'Op (M'.MutMsg s))))
new_PromisedAnswer'transform len struct = do
result <- C'.newList (U'.message struct) len
set_PromisedAnswer'transform struct result
pure result
newtype Provide msg = Provide_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Provide msg) where
fromStruct = pure . Provide_newtype_
instance C'.ToStruct msg (Provide msg) where
toStruct (Provide_newtype_ struct) = struct
instance C'.IsPtr msg (Provide msg) where
fromPtr msg ptr = Provide_newtype_ <$> C'.fromPtr msg ptr
toPtr (Provide_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Provide msg) where
newtype List msg (Provide msg) = List_Provide (U'.ListOf msg (U'.Struct msg))
length (List_Provide l) = U'.length l
index i (List_Provide l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Provide msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Provide (M'.MutMsg s)) where
setIndex (Provide_newtype_ elt) i (List_Provide l) = U'.setIndex elt i l
newList msg len = List_Provide <$> U'.allocCompositeList msg 1 2 len
instance U'.HasMessage (Provide msg) msg where
message (Provide_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Provide msg) msg where
messageDefault = Provide_newtype_ . U'.messageDefault
instance C'.Allocate s (Provide (M'.MutMsg s)) where
new msg = Provide_newtype_ <$> U'.allocStruct msg 1 2
instance C'.IsPtr msg (B'.List msg (Provide msg)) where
fromPtr msg ptr = List_Provide <$> C'.fromPtr msg ptr
toPtr (List_Provide l) = C'.toPtr l
get_Provide'questionId :: U'.ReadCtx m msg => Provide msg -> m Word32
get_Provide'questionId (Provide_newtype_ struct) = H'.getWordField struct 0 0 0
has_Provide'questionId :: U'.ReadCtx m msg => Provide msg -> m Bool
has_Provide'questionId(Provide_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Provide'questionId :: U'.RWCtx m s => Provide (M'.MutMsg s) -> Word32 -> m ()
set_Provide'questionId (Provide_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Provide'target :: U'.ReadCtx m msg => Provide msg -> m (MessageTarget msg)
get_Provide'target (Provide_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_Provide'target :: U'.ReadCtx m msg => Provide msg -> m Bool
has_Provide'target(Provide_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_Provide'target :: U'.RWCtx m s => Provide (M'.MutMsg s) -> (MessageTarget (M'.MutMsg s)) -> m ()
set_Provide'target (Provide_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
new_Provide'target :: U'.RWCtx m s => Provide (M'.MutMsg s) -> m ((MessageTarget (M'.MutMsg s)))
new_Provide'target struct = do
result <- C'.new (U'.message struct)
set_Provide'target struct result
pure result
get_Provide'recipient :: U'.ReadCtx m msg => Provide msg -> m (Maybe (U'.Ptr msg))
get_Provide'recipient (Provide_newtype_ struct) =
U'.getPtr 1 struct
>>= C'.fromPtr (U'.message struct)
has_Provide'recipient :: U'.ReadCtx m msg => Provide msg -> m Bool
has_Provide'recipient(Provide_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 1 struct
set_Provide'recipient :: U'.RWCtx m s => Provide (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Provide'recipient (Provide_newtype_ struct) value = U'.setPtr (C'.toPtr value) 1 struct
newtype Release msg = Release_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Release msg) where
fromStruct = pure . Release_newtype_
instance C'.ToStruct msg (Release msg) where
toStruct (Release_newtype_ struct) = struct
instance C'.IsPtr msg (Release msg) where
fromPtr msg ptr = Release_newtype_ <$> C'.fromPtr msg ptr
toPtr (Release_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Release msg) where
newtype List msg (Release msg) = List_Release (U'.ListOf msg (U'.Struct msg))
length (List_Release l) = U'.length l
index i (List_Release l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Release msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Release (M'.MutMsg s)) where
setIndex (Release_newtype_ elt) i (List_Release l) = U'.setIndex elt i l
newList msg len = List_Release <$> U'.allocCompositeList msg 1 0 len
instance U'.HasMessage (Release msg) msg where
message (Release_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Release msg) msg where
messageDefault = Release_newtype_ . U'.messageDefault
instance C'.Allocate s (Release (M'.MutMsg s)) where
new msg = Release_newtype_ <$> U'.allocStruct msg 1 0
instance C'.IsPtr msg (B'.List msg (Release msg)) where
fromPtr msg ptr = List_Release <$> C'.fromPtr msg ptr
toPtr (List_Release l) = C'.toPtr l
get_Release'id :: U'.ReadCtx m msg => Release msg -> m Word32
get_Release'id (Release_newtype_ struct) = H'.getWordField struct 0 0 0
has_Release'id :: U'.ReadCtx m msg => Release msg -> m Bool
has_Release'id(Release_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Release'id :: U'.RWCtx m s => Release (M'.MutMsg s) -> Word32 -> m ()
set_Release'id (Release_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Release'referenceCount :: U'.ReadCtx m msg => Release msg -> m Word32
get_Release'referenceCount (Release_newtype_ struct) = H'.getWordField struct 0 32 0
has_Release'referenceCount :: U'.ReadCtx m msg => Release msg -> m Bool
has_Release'referenceCount(Release_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Release'referenceCount :: U'.RWCtx m s => Release (M'.MutMsg s) -> Word32 -> m ()
set_Release'referenceCount (Release_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 32 0
newtype Resolve msg = Resolve_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Resolve msg) where
fromStruct = pure . Resolve_newtype_
instance C'.ToStruct msg (Resolve msg) where
toStruct (Resolve_newtype_ struct) = struct
instance C'.IsPtr msg (Resolve msg) where
fromPtr msg ptr = Resolve_newtype_ <$> C'.fromPtr msg ptr
toPtr (Resolve_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Resolve msg) where
newtype List msg (Resolve msg) = List_Resolve (U'.ListOf msg (U'.Struct msg))
length (List_Resolve l) = U'.length l
index i (List_Resolve l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Resolve msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Resolve (M'.MutMsg s)) where
setIndex (Resolve_newtype_ elt) i (List_Resolve l) = U'.setIndex elt i l
newList msg len = List_Resolve <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (Resolve msg) msg where
message (Resolve_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Resolve msg) msg where
messageDefault = Resolve_newtype_ . U'.messageDefault
instance C'.Allocate s (Resolve (M'.MutMsg s)) where
new msg = Resolve_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (Resolve msg)) where
fromPtr msg ptr = List_Resolve <$> C'.fromPtr msg ptr
toPtr (List_Resolve l) = C'.toPtr l
get_Resolve'promiseId :: U'.ReadCtx m msg => Resolve msg -> m Word32
get_Resolve'promiseId (Resolve_newtype_ struct) = H'.getWordField struct 0 0 0
has_Resolve'promiseId :: U'.ReadCtx m msg => Resolve msg -> m Bool
has_Resolve'promiseId(Resolve_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Resolve'promiseId :: U'.RWCtx m s => Resolve (M'.MutMsg s) -> Word32 -> m ()
set_Resolve'promiseId (Resolve_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Resolve'union' :: U'.ReadCtx m msg => Resolve msg -> m (Resolve' msg)
get_Resolve'union' (Resolve_newtype_ struct) = C'.fromStruct struct
has_Resolve'union' :: U'.ReadCtx m msg => Resolve msg -> m Bool
has_Resolve'union'(Resolve_newtype_ struct) = pure True
newtype Return msg = Return_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Return msg) where
fromStruct = pure . Return_newtype_
instance C'.ToStruct msg (Return msg) where
toStruct (Return_newtype_ struct) = struct
instance C'.IsPtr msg (Return msg) where
fromPtr msg ptr = Return_newtype_ <$> C'.fromPtr msg ptr
toPtr (Return_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Return msg) where
newtype List msg (Return msg) = List_Return (U'.ListOf msg (U'.Struct msg))
length (List_Return l) = U'.length l
index i (List_Return l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Return msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Return (M'.MutMsg s)) where
setIndex (Return_newtype_ elt) i (List_Return l) = U'.setIndex elt i l
newList msg len = List_Return <$> U'.allocCompositeList msg 2 1 len
instance U'.HasMessage (Return msg) msg where
message (Return_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Return msg) msg where
messageDefault = Return_newtype_ . U'.messageDefault
instance C'.Allocate s (Return (M'.MutMsg s)) where
new msg = Return_newtype_ <$> U'.allocStruct msg 2 1
instance C'.IsPtr msg (B'.List msg (Return msg)) where
fromPtr msg ptr = List_Return <$> C'.fromPtr msg ptr
toPtr (List_Return l) = C'.toPtr l
get_Return'answerId :: U'.ReadCtx m msg => Return msg -> m Word32
get_Return'answerId (Return_newtype_ struct) = H'.getWordField struct 0 0 0
has_Return'answerId :: U'.ReadCtx m msg => Return msg -> m Bool
has_Return'answerId(Return_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Return'answerId :: U'.RWCtx m s => Return (M'.MutMsg s) -> Word32 -> m ()
set_Return'answerId (Return_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
get_Return'releaseParamCaps :: U'.ReadCtx m msg => Return msg -> m Bool
get_Return'releaseParamCaps (Return_newtype_ struct) = H'.getWordField struct 0 32 1
has_Return'releaseParamCaps :: U'.ReadCtx m msg => Return msg -> m Bool
has_Return'releaseParamCaps(Return_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_Return'releaseParamCaps :: U'.RWCtx m s => Return (M'.MutMsg s) -> Bool -> m ()
set_Return'releaseParamCaps (Return_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word1) 0 32 1
get_Return'union' :: U'.ReadCtx m msg => Return msg -> m (Return' msg)
get_Return'union' (Return_newtype_ struct) = C'.fromStruct struct
has_Return'union' :: U'.ReadCtx m msg => Return msg -> m Bool
has_Return'union'(Return_newtype_ struct) = pure True
newtype ThirdPartyCapDescriptor msg = ThirdPartyCapDescriptor_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (ThirdPartyCapDescriptor msg) where
fromStruct = pure . ThirdPartyCapDescriptor_newtype_
instance C'.ToStruct msg (ThirdPartyCapDescriptor msg) where
toStruct (ThirdPartyCapDescriptor_newtype_ struct) = struct
instance C'.IsPtr msg (ThirdPartyCapDescriptor msg) where
fromPtr msg ptr = ThirdPartyCapDescriptor_newtype_ <$> C'.fromPtr msg ptr
toPtr (ThirdPartyCapDescriptor_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (ThirdPartyCapDescriptor msg) where
newtype List msg (ThirdPartyCapDescriptor msg) = List_ThirdPartyCapDescriptor (U'.ListOf msg (U'.Struct msg))
length (List_ThirdPartyCapDescriptor l) = U'.length l
index i (List_ThirdPartyCapDescriptor l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (ThirdPartyCapDescriptor msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (ThirdPartyCapDescriptor (M'.MutMsg s)) where
setIndex (ThirdPartyCapDescriptor_newtype_ elt) i (List_ThirdPartyCapDescriptor l) = U'.setIndex elt i l
newList msg len = List_ThirdPartyCapDescriptor <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (ThirdPartyCapDescriptor msg) msg where
message (ThirdPartyCapDescriptor_newtype_ struct) = U'.message struct
instance U'.MessageDefault (ThirdPartyCapDescriptor msg) msg where
messageDefault = ThirdPartyCapDescriptor_newtype_ . U'.messageDefault
instance C'.Allocate s (ThirdPartyCapDescriptor (M'.MutMsg s)) where
new msg = ThirdPartyCapDescriptor_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (ThirdPartyCapDescriptor msg)) where
fromPtr msg ptr = List_ThirdPartyCapDescriptor <$> C'.fromPtr msg ptr
toPtr (List_ThirdPartyCapDescriptor l) = C'.toPtr l
get_ThirdPartyCapDescriptor'id :: U'.ReadCtx m msg => ThirdPartyCapDescriptor msg -> m (Maybe (U'.Ptr msg))
get_ThirdPartyCapDescriptor'id (ThirdPartyCapDescriptor_newtype_ struct) =
U'.getPtr 0 struct
>>= C'.fromPtr (U'.message struct)
has_ThirdPartyCapDescriptor'id :: U'.ReadCtx m msg => ThirdPartyCapDescriptor msg -> m Bool
has_ThirdPartyCapDescriptor'id(ThirdPartyCapDescriptor_newtype_ struct) = Data.Maybe.isJust <$> U'.getPtr 0 struct
set_ThirdPartyCapDescriptor'id :: U'.RWCtx m s => ThirdPartyCapDescriptor (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_ThirdPartyCapDescriptor'id (ThirdPartyCapDescriptor_newtype_ struct) value = U'.setPtr (C'.toPtr value) 0 struct
get_ThirdPartyCapDescriptor'vineId :: U'.ReadCtx m msg => ThirdPartyCapDescriptor msg -> m Word32
get_ThirdPartyCapDescriptor'vineId (ThirdPartyCapDescriptor_newtype_ struct) = H'.getWordField struct 0 0 0
has_ThirdPartyCapDescriptor'vineId :: U'.ReadCtx m msg => ThirdPartyCapDescriptor msg -> m Bool
has_ThirdPartyCapDescriptor'vineId(ThirdPartyCapDescriptor_newtype_ struct) = pure $ 0 < U'.length (U'.dataSection struct)
set_ThirdPartyCapDescriptor'vineId :: U'.RWCtx m s => ThirdPartyCapDescriptor (M'.MutMsg s) -> Word32 -> m ()
set_ThirdPartyCapDescriptor'vineId (ThirdPartyCapDescriptor_newtype_ struct) value = H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
newtype Call'sendResultsTo msg = Call'sendResultsTo_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Call'sendResultsTo msg) where
fromStruct = pure . Call'sendResultsTo_newtype_
instance C'.ToStruct msg (Call'sendResultsTo msg) where
toStruct (Call'sendResultsTo_newtype_ struct) = struct
instance C'.IsPtr msg (Call'sendResultsTo msg) where
fromPtr msg ptr = Call'sendResultsTo_newtype_ <$> C'.fromPtr msg ptr
toPtr (Call'sendResultsTo_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Call'sendResultsTo msg) where
newtype List msg (Call'sendResultsTo msg) = List_Call'sendResultsTo (U'.ListOf msg (U'.Struct msg))
length (List_Call'sendResultsTo l) = U'.length l
index i (List_Call'sendResultsTo l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Call'sendResultsTo msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Call'sendResultsTo (M'.MutMsg s)) where
setIndex (Call'sendResultsTo_newtype_ elt) i (List_Call'sendResultsTo l) = U'.setIndex elt i l
newList msg len = List_Call'sendResultsTo <$> U'.allocCompositeList msg 3 3 len
instance U'.HasMessage (Call'sendResultsTo msg) msg where
message (Call'sendResultsTo_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Call'sendResultsTo msg) msg where
messageDefault = Call'sendResultsTo_newtype_ . U'.messageDefault
instance C'.Allocate s (Call'sendResultsTo (M'.MutMsg s)) where
new msg = Call'sendResultsTo_newtype_ <$> U'.allocStruct msg 3 3
instance C'.IsPtr msg (B'.List msg (Call'sendResultsTo msg)) where
fromPtr msg ptr = List_Call'sendResultsTo <$> C'.fromPtr msg ptr
toPtr (List_Call'sendResultsTo l) = C'.toPtr l
data Call'sendResultsTo' msg =
Call'sendResultsTo'caller |
Call'sendResultsTo'yourself |
Call'sendResultsTo'thirdParty (Maybe (U'.Ptr msg)) |
Call'sendResultsTo'unknown' Word16
get_Call'sendResultsTo' :: U'.ReadCtx m msg => Call'sendResultsTo msg -> m (Call'sendResultsTo' msg)
get_Call'sendResultsTo' (Call'sendResultsTo_newtype_ struct) = C'.fromStruct struct
has_Call'sendResultsTo' :: U'.ReadCtx m msg => Call'sendResultsTo msg -> m Bool
has_Call'sendResultsTo'(Call'sendResultsTo_newtype_ struct) = pure True
set_Call'sendResultsTo'caller :: U'.RWCtx m s => Call'sendResultsTo (M'.MutMsg s) -> m ()
set_Call'sendResultsTo'caller (Call'sendResultsTo_newtype_ struct) = H'.setWordField struct (0 :: Word16) 0 48 0
set_Call'sendResultsTo'yourself :: U'.RWCtx m s => Call'sendResultsTo (M'.MutMsg s) -> m ()
set_Call'sendResultsTo'yourself (Call'sendResultsTo_newtype_ struct) = H'.setWordField struct (1 :: Word16) 0 48 0
set_Call'sendResultsTo'thirdParty :: U'.RWCtx m s => Call'sendResultsTo (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Call'sendResultsTo'thirdParty(Call'sendResultsTo_newtype_ struct) value = do
H'.setWordField struct (2 :: Word16) 0 48 0
U'.setPtr (C'.toPtr value) 2 struct
set_Call'sendResultsTo'unknown' :: U'.RWCtx m s => Call'sendResultsTo (M'.MutMsg s) -> Word16 -> m ()
set_Call'sendResultsTo'unknown'(Call'sendResultsTo_newtype_ struct) tagValue = H'.setWordField struct (tagValue :: Word16) 0 48 0
instance C'.FromStruct msg (Call'sendResultsTo' msg) where
fromStruct struct = do
tag <- H'.getWordField struct 0 48 0
case tag of
2 -> Call'sendResultsTo'thirdParty <$> (U'.getPtr 2 struct >>= C'.fromPtr (U'.message struct))
1 -> pure Call'sendResultsTo'yourself
0 -> pure Call'sendResultsTo'caller
_ -> pure $ Call'sendResultsTo'unknown' tag
newtype Disembargo'context msg = Disembargo'context_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Disembargo'context msg) where
fromStruct = pure . Disembargo'context_newtype_
instance C'.ToStruct msg (Disembargo'context msg) where
toStruct (Disembargo'context_newtype_ struct) = struct
instance C'.IsPtr msg (Disembargo'context msg) where
fromPtr msg ptr = Disembargo'context_newtype_ <$> C'.fromPtr msg ptr
toPtr (Disembargo'context_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Disembargo'context msg) where
newtype List msg (Disembargo'context msg) = List_Disembargo'context (U'.ListOf msg (U'.Struct msg))
length (List_Disembargo'context l) = U'.length l
index i (List_Disembargo'context l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Disembargo'context msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Disembargo'context (M'.MutMsg s)) where
setIndex (Disembargo'context_newtype_ elt) i (List_Disembargo'context l) = U'.setIndex elt i l
newList msg len = List_Disembargo'context <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (Disembargo'context msg) msg where
message (Disembargo'context_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Disembargo'context msg) msg where
messageDefault = Disembargo'context_newtype_ . U'.messageDefault
instance C'.Allocate s (Disembargo'context (M'.MutMsg s)) where
new msg = Disembargo'context_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (Disembargo'context msg)) where
fromPtr msg ptr = List_Disembargo'context <$> C'.fromPtr msg ptr
toPtr (List_Disembargo'context l) = C'.toPtr l
data Disembargo'context' msg =
Disembargo'context'senderLoopback Word32 |
Disembargo'context'receiverLoopback Word32 |
Disembargo'context'accept |
Disembargo'context'provide Word32 |
Disembargo'context'unknown' Word16
get_Disembargo'context' :: U'.ReadCtx m msg => Disembargo'context msg -> m (Disembargo'context' msg)
get_Disembargo'context' (Disembargo'context_newtype_ struct) = C'.fromStruct struct
has_Disembargo'context' :: U'.ReadCtx m msg => Disembargo'context msg -> m Bool
has_Disembargo'context'(Disembargo'context_newtype_ struct) = pure True
set_Disembargo'context'senderLoopback :: U'.RWCtx m s => Disembargo'context (M'.MutMsg s) -> Word32 -> m ()
set_Disembargo'context'senderLoopback (Disembargo'context_newtype_ struct) value = do
H'.setWordField struct (0 :: Word16) 0 32 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
set_Disembargo'context'receiverLoopback :: U'.RWCtx m s => Disembargo'context (M'.MutMsg s) -> Word32 -> m ()
set_Disembargo'context'receiverLoopback (Disembargo'context_newtype_ struct) value = do
H'.setWordField struct (1 :: Word16) 0 32 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
set_Disembargo'context'accept :: U'.RWCtx m s => Disembargo'context (M'.MutMsg s) -> m ()
set_Disembargo'context'accept (Disembargo'context_newtype_ struct) = H'.setWordField struct (2 :: Word16) 0 32 0
set_Disembargo'context'provide :: U'.RWCtx m s => Disembargo'context (M'.MutMsg s) -> Word32 -> m ()
set_Disembargo'context'provide (Disembargo'context_newtype_ struct) value = do
H'.setWordField struct (3 :: Word16) 0 32 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 0 0 0
set_Disembargo'context'unknown' :: U'.RWCtx m s => Disembargo'context (M'.MutMsg s) -> Word16 -> m ()
set_Disembargo'context'unknown'(Disembargo'context_newtype_ struct) tagValue = H'.setWordField struct (tagValue :: Word16) 0 32 0
instance C'.FromStruct msg (Disembargo'context' msg) where
fromStruct struct = do
tag <- H'.getWordField struct 0 32 0
case tag of
3 -> Disembargo'context'provide <$> H'.getWordField struct 0 0 0
2 -> pure Disembargo'context'accept
1 -> Disembargo'context'receiverLoopback <$> H'.getWordField struct 0 0 0
0 -> Disembargo'context'senderLoopback <$> H'.getWordField struct 0 0 0
_ -> pure $ Disembargo'context'unknown' tag
data Exception'Type =
Exception'Type'failed |
Exception'Type'overloaded |
Exception'Type'disconnected |
Exception'Type'unimplemented |
Exception'Type'unknown' Word16
deriving(Show, Read, Eq, Generic)
instance Enum Exception'Type where
toEnum = C'.fromWord . fromIntegral
fromEnum = fromIntegral . C'.toWord
instance C'.IsWord Exception'Type where
fromWord n = go (fromIntegral n :: Word16) where
go 3 = Exception'Type'unimplemented
go 2 = Exception'Type'disconnected
go 1 = Exception'Type'overloaded
go 0 = Exception'Type'failed
go tag = Exception'Type'unknown' (fromIntegral tag)
toWord Exception'Type'unimplemented = 3
toWord Exception'Type'disconnected = 2
toWord Exception'Type'overloaded = 1
toWord Exception'Type'failed = 0
toWord (Exception'Type'unknown' tag) = fromIntegral tag
instance B'.ListElem msg Exception'Type where
newtype List msg Exception'Type = List_Exception'Type (U'.ListOf msg Word16)
length (List_Exception'Type l) = U'.length l
index i (List_Exception'Type l) = (C'.fromWord . fromIntegral) <$> U'.index i l
instance B'.MutListElem s Exception'Type where
setIndex elt i (List_Exception'Type l) = U'.setIndex (fromIntegral $ C'.toWord elt) i l
newList msg size = List_Exception'Type <$> U'.allocList16 msg size
instance C'.IsPtr msg (B'.List msg Exception'Type) where
fromPtr msg ptr = List_Exception'Type <$> C'.fromPtr msg ptr
toPtr (List_Exception'Type l) = C'.toPtr l
newtype PromisedAnswer'Op msg = PromisedAnswer'Op_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (PromisedAnswer'Op msg) where
fromStruct = pure . PromisedAnswer'Op_newtype_
instance C'.ToStruct msg (PromisedAnswer'Op msg) where
toStruct (PromisedAnswer'Op_newtype_ struct) = struct
instance C'.IsPtr msg (PromisedAnswer'Op msg) where
fromPtr msg ptr = PromisedAnswer'Op_newtype_ <$> C'.fromPtr msg ptr
toPtr (PromisedAnswer'Op_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (PromisedAnswer'Op msg) where
newtype List msg (PromisedAnswer'Op msg) = List_PromisedAnswer'Op (U'.ListOf msg (U'.Struct msg))
length (List_PromisedAnswer'Op l) = U'.length l
index i (List_PromisedAnswer'Op l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (PromisedAnswer'Op msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (PromisedAnswer'Op (M'.MutMsg s)) where
setIndex (PromisedAnswer'Op_newtype_ elt) i (List_PromisedAnswer'Op l) = U'.setIndex elt i l
newList msg len = List_PromisedAnswer'Op <$> U'.allocCompositeList msg 1 0 len
instance U'.HasMessage (PromisedAnswer'Op msg) msg where
message (PromisedAnswer'Op_newtype_ struct) = U'.message struct
instance U'.MessageDefault (PromisedAnswer'Op msg) msg where
messageDefault = PromisedAnswer'Op_newtype_ . U'.messageDefault
instance C'.Allocate s (PromisedAnswer'Op (M'.MutMsg s)) where
new msg = PromisedAnswer'Op_newtype_ <$> U'.allocStruct msg 1 0
instance C'.IsPtr msg (B'.List msg (PromisedAnswer'Op msg)) where
fromPtr msg ptr = List_PromisedAnswer'Op <$> C'.fromPtr msg ptr
toPtr (List_PromisedAnswer'Op l) = C'.toPtr l
data PromisedAnswer'Op' msg =
PromisedAnswer'Op'noop |
PromisedAnswer'Op'getPointerField Word16 |
PromisedAnswer'Op'unknown' Word16
get_PromisedAnswer'Op' :: U'.ReadCtx m msg => PromisedAnswer'Op msg -> m (PromisedAnswer'Op' msg)
get_PromisedAnswer'Op' (PromisedAnswer'Op_newtype_ struct) = C'.fromStruct struct
has_PromisedAnswer'Op' :: U'.ReadCtx m msg => PromisedAnswer'Op msg -> m Bool
has_PromisedAnswer'Op'(PromisedAnswer'Op_newtype_ struct) = pure True
set_PromisedAnswer'Op'noop :: U'.RWCtx m s => PromisedAnswer'Op (M'.MutMsg s) -> m ()
set_PromisedAnswer'Op'noop (PromisedAnswer'Op_newtype_ struct) = H'.setWordField struct (0 :: Word16) 0 0 0
set_PromisedAnswer'Op'getPointerField :: U'.RWCtx m s => PromisedAnswer'Op (M'.MutMsg s) -> Word16 -> m ()
set_PromisedAnswer'Op'getPointerField (PromisedAnswer'Op_newtype_ struct) value = do
H'.setWordField struct (1 :: Word16) 0 0 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word16) 0 16 0
set_PromisedAnswer'Op'unknown' :: U'.RWCtx m s => PromisedAnswer'Op (M'.MutMsg s) -> Word16 -> m ()
set_PromisedAnswer'Op'unknown'(PromisedAnswer'Op_newtype_ struct) tagValue = H'.setWordField struct (tagValue :: Word16) 0 0 0
instance C'.FromStruct msg (PromisedAnswer'Op' msg) where
fromStruct struct = do
tag <- H'.getWordField struct 0 0 0
case tag of
1 -> PromisedAnswer'Op'getPointerField <$> H'.getWordField struct 0 16 0
0 -> pure PromisedAnswer'Op'noop
_ -> pure $ PromisedAnswer'Op'unknown' tag
newtype Resolve' msg = Resolve'_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Resolve' msg) where
fromStruct = pure . Resolve'_newtype_
instance C'.ToStruct msg (Resolve' msg) where
toStruct (Resolve'_newtype_ struct) = struct
instance C'.IsPtr msg (Resolve' msg) where
fromPtr msg ptr = Resolve'_newtype_ <$> C'.fromPtr msg ptr
toPtr (Resolve'_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Resolve' msg) where
newtype List msg (Resolve' msg) = List_Resolve' (U'.ListOf msg (U'.Struct msg))
length (List_Resolve' l) = U'.length l
index i (List_Resolve' l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Resolve' msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Resolve' (M'.MutMsg s)) where
setIndex (Resolve'_newtype_ elt) i (List_Resolve' l) = U'.setIndex elt i l
newList msg len = List_Resolve' <$> U'.allocCompositeList msg 1 1 len
instance U'.HasMessage (Resolve' msg) msg where
message (Resolve'_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Resolve' msg) msg where
messageDefault = Resolve'_newtype_ . U'.messageDefault
instance C'.Allocate s (Resolve' (M'.MutMsg s)) where
new msg = Resolve'_newtype_ <$> U'.allocStruct msg 1 1
instance C'.IsPtr msg (B'.List msg (Resolve' msg)) where
fromPtr msg ptr = List_Resolve' <$> C'.fromPtr msg ptr
toPtr (List_Resolve' l) = C'.toPtr l
data Resolve'' msg =
Resolve'cap (CapDescriptor msg) |
Resolve'exception (Exception msg) |
Resolve'unknown' Word16
get_Resolve'' :: U'.ReadCtx m msg => Resolve' msg -> m (Resolve'' msg)
get_Resolve'' (Resolve'_newtype_ struct) = C'.fromStruct struct
has_Resolve'' :: U'.ReadCtx m msg => Resolve' msg -> m Bool
has_Resolve''(Resolve'_newtype_ struct) = pure True
set_Resolve'cap :: U'.RWCtx m s => Resolve' (M'.MutMsg s) -> (CapDescriptor (M'.MutMsg s)) -> m ()
set_Resolve'cap(Resolve'_newtype_ struct) value = do
H'.setWordField struct (0 :: Word16) 0 32 0
U'.setPtr (C'.toPtr value) 0 struct
new_Resolve'cap :: U'.RWCtx m s => Resolve' (M'.MutMsg s) -> m ((CapDescriptor (M'.MutMsg s)))
new_Resolve'cap struct = do
result <- C'.new (U'.message struct)
set_Resolve'cap struct result
pure result
set_Resolve'exception :: U'.RWCtx m s => Resolve' (M'.MutMsg s) -> (Exception (M'.MutMsg s)) -> m ()
set_Resolve'exception(Resolve'_newtype_ struct) value = do
H'.setWordField struct (1 :: Word16) 0 32 0
U'.setPtr (C'.toPtr value) 0 struct
new_Resolve'exception :: U'.RWCtx m s => Resolve' (M'.MutMsg s) -> m ((Exception (M'.MutMsg s)))
new_Resolve'exception struct = do
result <- C'.new (U'.message struct)
set_Resolve'exception struct result
pure result
set_Resolve'unknown' :: U'.RWCtx m s => Resolve' (M'.MutMsg s) -> Word16 -> m ()
set_Resolve'unknown'(Resolve'_newtype_ struct) tagValue = H'.setWordField struct (tagValue :: Word16) 0 32 0
instance C'.FromStruct msg (Resolve'' msg) where
fromStruct struct = do
tag <- H'.getWordField struct 0 32 0
case tag of
1 -> Resolve'exception <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
0 -> Resolve'cap <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
_ -> pure $ Resolve'unknown' tag
newtype Return' msg = Return'_newtype_ (U'.Struct msg)
instance C'.FromStruct msg (Return' msg) where
fromStruct = pure . Return'_newtype_
instance C'.ToStruct msg (Return' msg) where
toStruct (Return'_newtype_ struct) = struct
instance C'.IsPtr msg (Return' msg) where
fromPtr msg ptr = Return'_newtype_ <$> C'.fromPtr msg ptr
toPtr (Return'_newtype_ struct) = C'.toPtr struct
instance B'.ListElem msg (Return' msg) where
newtype List msg (Return' msg) = List_Return' (U'.ListOf msg (U'.Struct msg))
length (List_Return' l) = U'.length l
index i (List_Return' l) = U'.index i l >>= (let {go :: U'.ReadCtx m msg => U'.Struct msg -> m (Return' msg); go = C'.fromStruct} in go)
instance B'.MutListElem s (Return' (M'.MutMsg s)) where
setIndex (Return'_newtype_ elt) i (List_Return' l) = U'.setIndex elt i l
newList msg len = List_Return' <$> U'.allocCompositeList msg 2 1 len
instance U'.HasMessage (Return' msg) msg where
message (Return'_newtype_ struct) = U'.message struct
instance U'.MessageDefault (Return' msg) msg where
messageDefault = Return'_newtype_ . U'.messageDefault
instance C'.Allocate s (Return' (M'.MutMsg s)) where
new msg = Return'_newtype_ <$> U'.allocStruct msg 2 1
instance C'.IsPtr msg (B'.List msg (Return' msg)) where
fromPtr msg ptr = List_Return' <$> C'.fromPtr msg ptr
toPtr (List_Return' l) = C'.toPtr l
data Return'' msg =
Return'results (Payload msg) |
Return'exception (Exception msg) |
Return'canceled |
Return'resultsSentElsewhere |
Return'takeFromOtherQuestion Word32 |
Return'acceptFromThirdParty (Maybe (U'.Ptr msg)) |
Return'unknown' Word16
get_Return'' :: U'.ReadCtx m msg => Return' msg -> m (Return'' msg)
get_Return'' (Return'_newtype_ struct) = C'.fromStruct struct
has_Return'' :: U'.ReadCtx m msg => Return' msg -> m Bool
has_Return''(Return'_newtype_ struct) = pure True
set_Return'results :: U'.RWCtx m s => Return' (M'.MutMsg s) -> (Payload (M'.MutMsg s)) -> m ()
set_Return'results(Return'_newtype_ struct) value = do
H'.setWordField struct (0 :: Word16) 0 48 0
U'.setPtr (C'.toPtr value) 0 struct
new_Return'results :: U'.RWCtx m s => Return' (M'.MutMsg s) -> m ((Payload (M'.MutMsg s)))
new_Return'results struct = do
result <- C'.new (U'.message struct)
set_Return'results struct result
pure result
set_Return'exception :: U'.RWCtx m s => Return' (M'.MutMsg s) -> (Exception (M'.MutMsg s)) -> m ()
set_Return'exception(Return'_newtype_ struct) value = do
H'.setWordField struct (1 :: Word16) 0 48 0
U'.setPtr (C'.toPtr value) 0 struct
new_Return'exception :: U'.RWCtx m s => Return' (M'.MutMsg s) -> m ((Exception (M'.MutMsg s)))
new_Return'exception struct = do
result <- C'.new (U'.message struct)
set_Return'exception struct result
pure result
set_Return'canceled :: U'.RWCtx m s => Return' (M'.MutMsg s) -> m ()
set_Return'canceled (Return'_newtype_ struct) = H'.setWordField struct (2 :: Word16) 0 48 0
set_Return'resultsSentElsewhere :: U'.RWCtx m s => Return' (M'.MutMsg s) -> m ()
set_Return'resultsSentElsewhere (Return'_newtype_ struct) = H'.setWordField struct (3 :: Word16) 0 48 0
set_Return'takeFromOtherQuestion :: U'.RWCtx m s => Return' (M'.MutMsg s) -> Word32 -> m ()
set_Return'takeFromOtherQuestion (Return'_newtype_ struct) value = do
H'.setWordField struct (4 :: Word16) 0 48 0
H'.setWordField struct (fromIntegral (C'.toWord value) :: Word32) 1 0 0
set_Return'acceptFromThirdParty :: U'.RWCtx m s => Return' (M'.MutMsg s) -> (Maybe (U'.Ptr (M'.MutMsg s))) -> m ()
set_Return'acceptFromThirdParty(Return'_newtype_ struct) value = do
H'.setWordField struct (5 :: Word16) 0 48 0
U'.setPtr (C'.toPtr value) 0 struct
set_Return'unknown' :: U'.RWCtx m s => Return' (M'.MutMsg s) -> Word16 -> m ()
set_Return'unknown'(Return'_newtype_ struct) tagValue = H'.setWordField struct (tagValue :: Word16) 0 48 0
instance C'.FromStruct msg (Return'' msg) where
fromStruct struct = do
tag <- H'.getWordField struct 0 48 0
case tag of
5 -> Return'acceptFromThirdParty <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
4 -> Return'takeFromOtherQuestion <$> H'.getWordField struct 1 0 0
3 -> pure Return'resultsSentElsewhere
2 -> pure Return'canceled
1 -> Return'exception <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
0 -> Return'results <$> (U'.getPtr 0 struct >>= C'.fromPtr (U'.message struct))
_ -> pure $ Return'unknown' tag