{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.OutputMessage
(
OutputMessage(..) ,
newZeroOutputMessage ,
noOutputMessage ,
#if defined(ENABLE_OVERLOADING)
ResolveOutputMessageMethod ,
#endif
clearOutputMessageAddress ,
getOutputMessageAddress ,
#if defined(ENABLE_OVERLOADING)
outputMessage_address ,
#endif
setOutputMessageAddress ,
getOutputMessageBytesSent ,
#if defined(ENABLE_OVERLOADING)
outputMessage_bytesSent ,
#endif
setOutputMessageBytesSent ,
getOutputMessageNumControlMessages ,
#if defined(ENABLE_OVERLOADING)
outputMessage_numControlMessages ,
#endif
setOutputMessageNumControlMessages ,
getOutputMessageNumVectors ,
#if defined(ENABLE_OVERLOADING)
outputMessage_numVectors ,
#endif
setOutputMessageNumVectors ,
clearOutputMessageVectors ,
getOutputMessageVectors ,
#if defined(ENABLE_OVERLOADING)
outputMessage_vectors ,
#endif
setOutputMessageVectors ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector
newtype OutputMessage = OutputMessage (ManagedPtr OutputMessage)
deriving (OutputMessage -> OutputMessage -> Bool
(OutputMessage -> OutputMessage -> Bool)
-> (OutputMessage -> OutputMessage -> Bool) -> Eq OutputMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputMessage -> OutputMessage -> Bool
$c/= :: OutputMessage -> OutputMessage -> Bool
== :: OutputMessage -> OutputMessage -> Bool
$c== :: OutputMessage -> OutputMessage -> Bool
Eq)
instance WrappedPtr OutputMessage where
wrappedPtrCalloc :: IO (Ptr OutputMessage)
wrappedPtrCalloc = Int -> IO (Ptr OutputMessage)
forall a. Int -> IO (Ptr a)
callocBytes 40
wrappedPtrCopy :: OutputMessage -> IO OutputMessage
wrappedPtrCopy = \p :: OutputMessage
p -> OutputMessage
-> (Ptr OutputMessage -> IO OutputMessage) -> IO OutputMessage
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
p (Int -> Ptr OutputMessage -> IO (Ptr OutputMessage)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 40 (Ptr OutputMessage -> IO (Ptr OutputMessage))
-> (Ptr OutputMessage -> IO OutputMessage)
-> Ptr OutputMessage
-> IO OutputMessage
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr OutputMessage -> OutputMessage)
-> Ptr OutputMessage -> IO OutputMessage
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr OutputMessage -> OutputMessage
OutputMessage)
wrappedPtrFree :: Maybe (GDestroyNotify OutputMessage)
wrappedPtrFree = GDestroyNotify OutputMessage
-> Maybe (GDestroyNotify OutputMessage)
forall a. a -> Maybe a
Just GDestroyNotify OutputMessage
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroOutputMessage :: MonadIO m => m OutputMessage
newZeroOutputMessage :: m OutputMessage
newZeroOutputMessage = IO OutputMessage -> m OutputMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OutputMessage -> m OutputMessage)
-> IO OutputMessage -> m OutputMessage
forall a b. (a -> b) -> a -> b
$ IO (Ptr OutputMessage)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr OutputMessage)
-> (Ptr OutputMessage -> IO OutputMessage) -> IO OutputMessage
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr OutputMessage -> OutputMessage)
-> Ptr OutputMessage -> IO OutputMessage
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr OutputMessage -> OutputMessage
OutputMessage
instance tag ~ 'AttrSet => Constructible OutputMessage tag where
new :: (ManagedPtr OutputMessage -> OutputMessage)
-> [AttrOp OutputMessage tag] -> m OutputMessage
new _ attrs :: [AttrOp OutputMessage tag]
attrs = do
OutputMessage
o <- m OutputMessage
forall (m :: * -> *). MonadIO m => m OutputMessage
newZeroOutputMessage
OutputMessage -> [AttrOp OutputMessage 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set OutputMessage
o [AttrOp OutputMessage tag]
[AttrOp OutputMessage 'AttrSet]
attrs
OutputMessage -> m OutputMessage
forall (m :: * -> *) a. Monad m => a -> m a
return OutputMessage
o
noOutputMessage :: Maybe OutputMessage
noOutputMessage :: Maybe OutputMessage
noOutputMessage = Maybe OutputMessage
forall a. Maybe a
Nothing
getOutputMessageAddress :: MonadIO m => OutputMessage -> m (Maybe Gio.SocketAddress.SocketAddress)
getOutputMessageAddress :: OutputMessage -> m (Maybe SocketAddress)
getOutputMessageAddress s :: OutputMessage
s = IO (Maybe SocketAddress) -> m (Maybe SocketAddress)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe SocketAddress) -> m (Maybe SocketAddress))
-> IO (Maybe SocketAddress) -> m (Maybe SocketAddress)
forall a b. (a -> b) -> a -> b
$ OutputMessage
-> (Ptr OutputMessage -> IO (Maybe SocketAddress))
-> IO (Maybe SocketAddress)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO (Maybe SocketAddress))
-> IO (Maybe SocketAddress))
-> (Ptr OutputMessage -> IO (Maybe SocketAddress))
-> IO (Maybe SocketAddress)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr SocketAddress
val <- Ptr (Ptr SocketAddress) -> IO (Ptr SocketAddress)
forall a. Storable a => Ptr a -> IO a
peek (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr (Ptr SocketAddress)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO (Ptr Gio.SocketAddress.SocketAddress)
Maybe SocketAddress
result <- Ptr SocketAddress
-> (Ptr SocketAddress -> IO SocketAddress)
-> IO (Maybe SocketAddress)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr SocketAddress
val ((Ptr SocketAddress -> IO SocketAddress)
-> IO (Maybe SocketAddress))
-> (Ptr SocketAddress -> IO SocketAddress)
-> IO (Maybe SocketAddress)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr SocketAddress
val' -> do
SocketAddress
val'' <- ((ManagedPtr SocketAddress -> SocketAddress)
-> Ptr SocketAddress -> IO SocketAddress
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr SocketAddress -> SocketAddress
Gio.SocketAddress.SocketAddress) Ptr SocketAddress
val'
SocketAddress -> IO SocketAddress
forall (m :: * -> *) a. Monad m => a -> m a
return SocketAddress
val''
Maybe SocketAddress -> IO (Maybe SocketAddress)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SocketAddress
result
setOutputMessageAddress :: MonadIO m => OutputMessage -> Ptr Gio.SocketAddress.SocketAddress -> m ()
setOutputMessageAddress :: OutputMessage -> Ptr SocketAddress -> m ()
setOutputMessageAddress s :: OutputMessage
s val :: Ptr SocketAddress
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO ()) -> IO ())
-> (Ptr OutputMessage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr (Ptr SocketAddress) -> Ptr SocketAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr (Ptr SocketAddress)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr SocketAddress
val :: Ptr Gio.SocketAddress.SocketAddress)
clearOutputMessageAddress :: MonadIO m => OutputMessage -> m ()
clearOutputMessageAddress :: OutputMessage -> m ()
clearOutputMessageAddress s :: OutputMessage
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO ()) -> IO ())
-> (Ptr OutputMessage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr (Ptr SocketAddress) -> Ptr SocketAddress -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr (Ptr SocketAddress)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr SocketAddress
forall a. Ptr a
FP.nullPtr :: Ptr Gio.SocketAddress.SocketAddress)
#if defined(ENABLE_OVERLOADING)
data OutputMessageAddressFieldInfo
instance AttrInfo OutputMessageAddressFieldInfo where
type AttrBaseTypeConstraint OutputMessageAddressFieldInfo = (~) OutputMessage
type AttrAllowedOps OutputMessageAddressFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint OutputMessageAddressFieldInfo = (~) (Ptr Gio.SocketAddress.SocketAddress)
type AttrTransferTypeConstraint OutputMessageAddressFieldInfo = (~)(Ptr Gio.SocketAddress.SocketAddress)
type AttrTransferType OutputMessageAddressFieldInfo = (Ptr Gio.SocketAddress.SocketAddress)
type AttrGetType OutputMessageAddressFieldInfo = Maybe Gio.SocketAddress.SocketAddress
type AttrLabel OutputMessageAddressFieldInfo = "address"
type AttrOrigin OutputMessageAddressFieldInfo = OutputMessage
attrGet = getOutputMessageAddress
attrSet = setOutputMessageAddress
attrConstruct = undefined
attrClear = clearOutputMessageAddress
attrTransfer _ v = do
return v
outputMessage_address :: AttrLabelProxy "address"
outputMessage_address = AttrLabelProxy
#endif
getOutputMessageVectors :: MonadIO m => OutputMessage -> m (Maybe Gio.OutputVector.OutputVector)
getOutputMessageVectors :: OutputMessage -> m (Maybe OutputVector)
getOutputMessageVectors s :: OutputMessage
s = IO (Maybe OutputVector) -> m (Maybe OutputVector)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe OutputVector) -> m (Maybe OutputVector))
-> IO (Maybe OutputVector) -> m (Maybe OutputVector)
forall a b. (a -> b) -> a -> b
$ OutputMessage
-> (Ptr OutputMessage -> IO (Maybe OutputVector))
-> IO (Maybe OutputVector)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO (Maybe OutputVector))
-> IO (Maybe OutputVector))
-> (Ptr OutputMessage -> IO (Maybe OutputVector))
-> IO (Maybe OutputVector)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr OutputVector
val <- Ptr (Ptr OutputVector) -> IO (Ptr OutputVector)
forall a. Storable a => Ptr a -> IO a
peek (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr (Ptr OutputVector)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO (Ptr Gio.OutputVector.OutputVector)
Maybe OutputVector
result <- Ptr OutputVector
-> (Ptr OutputVector -> IO OutputVector) -> IO (Maybe OutputVector)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr OutputVector
val ((Ptr OutputVector -> IO OutputVector) -> IO (Maybe OutputVector))
-> (Ptr OutputVector -> IO OutputVector) -> IO (Maybe OutputVector)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr OutputVector
val' -> do
OutputVector
val'' <- ((ManagedPtr OutputVector -> OutputVector)
-> Ptr OutputVector -> IO OutputVector
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr OutputVector -> OutputVector
Gio.OutputVector.OutputVector) Ptr OutputVector
val'
OutputVector -> IO OutputVector
forall (m :: * -> *) a. Monad m => a -> m a
return OutputVector
val''
Maybe OutputVector -> IO (Maybe OutputVector)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OutputVector
result
setOutputMessageVectors :: MonadIO m => OutputMessage -> Ptr Gio.OutputVector.OutputVector -> m ()
setOutputMessageVectors :: OutputMessage -> Ptr OutputVector -> m ()
setOutputMessageVectors s :: OutputMessage
s val :: Ptr OutputVector
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO ()) -> IO ())
-> (Ptr OutputMessage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr (Ptr OutputVector) -> Ptr OutputVector -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr (Ptr OutputVector)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr OutputVector
val :: Ptr Gio.OutputVector.OutputVector)
clearOutputMessageVectors :: MonadIO m => OutputMessage -> m ()
clearOutputMessageVectors :: OutputMessage -> m ()
clearOutputMessageVectors s :: OutputMessage
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO ()) -> IO ())
-> (Ptr OutputMessage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr (Ptr OutputVector) -> Ptr OutputVector -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr (Ptr OutputVector)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr OutputVector
forall a. Ptr a
FP.nullPtr :: Ptr Gio.OutputVector.OutputVector)
#if defined(ENABLE_OVERLOADING)
data OutputMessageVectorsFieldInfo
instance AttrInfo OutputMessageVectorsFieldInfo where
type AttrBaseTypeConstraint OutputMessageVectorsFieldInfo = (~) OutputMessage
type AttrAllowedOps OutputMessageVectorsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint OutputMessageVectorsFieldInfo = (~) (Ptr Gio.OutputVector.OutputVector)
type AttrTransferTypeConstraint OutputMessageVectorsFieldInfo = (~)(Ptr Gio.OutputVector.OutputVector)
type AttrTransferType OutputMessageVectorsFieldInfo = (Ptr Gio.OutputVector.OutputVector)
type AttrGetType OutputMessageVectorsFieldInfo = Maybe Gio.OutputVector.OutputVector
type AttrLabel OutputMessageVectorsFieldInfo = "vectors"
type AttrOrigin OutputMessageVectorsFieldInfo = OutputMessage
attrGet = getOutputMessageVectors
attrSet = setOutputMessageVectors
attrConstruct = undefined
attrClear = clearOutputMessageVectors
attrTransfer _ v = do
return v
outputMessage_vectors :: AttrLabelProxy "vectors"
outputMessage_vectors = AttrLabelProxy
#endif
getOutputMessageNumVectors :: MonadIO m => OutputMessage -> m Word32
getOutputMessageNumVectors :: OutputMessage -> m Word32
getOutputMessageNumVectors s :: OutputMessage
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO Word32) -> IO Word32)
-> (Ptr OutputMessage -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setOutputMessageNumVectors :: MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageNumVectors :: OutputMessage -> Word32 -> m ()
setOutputMessageNumVectors s :: OutputMessage
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO ()) -> IO ())
-> (Ptr OutputMessage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data OutputMessageNumVectorsFieldInfo
instance AttrInfo OutputMessageNumVectorsFieldInfo where
type AttrBaseTypeConstraint OutputMessageNumVectorsFieldInfo = (~) OutputMessage
type AttrAllowedOps OutputMessageNumVectorsFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OutputMessageNumVectorsFieldInfo = (~) Word32
type AttrTransferTypeConstraint OutputMessageNumVectorsFieldInfo = (~)Word32
type AttrTransferType OutputMessageNumVectorsFieldInfo = Word32
type AttrGetType OutputMessageNumVectorsFieldInfo = Word32
type AttrLabel OutputMessageNumVectorsFieldInfo = "num_vectors"
type AttrOrigin OutputMessageNumVectorsFieldInfo = OutputMessage
attrGet = getOutputMessageNumVectors
attrSet = setOutputMessageNumVectors
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
outputMessage_numVectors :: AttrLabelProxy "numVectors"
outputMessage_numVectors = AttrLabelProxy
#endif
getOutputMessageBytesSent :: MonadIO m => OutputMessage -> m Word32
getOutputMessageBytesSent :: OutputMessage -> m Word32
getOutputMessageBytesSent s :: OutputMessage
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO Word32) -> IO Word32)
-> (Ptr OutputMessage -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setOutputMessageBytesSent :: MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageBytesSent :: OutputMessage -> Word32 -> m ()
setOutputMessageBytesSent s :: OutputMessage
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO ()) -> IO ())
-> (Ptr OutputMessage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data OutputMessageBytesSentFieldInfo
instance AttrInfo OutputMessageBytesSentFieldInfo where
type AttrBaseTypeConstraint OutputMessageBytesSentFieldInfo = (~) OutputMessage
type AttrAllowedOps OutputMessageBytesSentFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OutputMessageBytesSentFieldInfo = (~) Word32
type AttrTransferTypeConstraint OutputMessageBytesSentFieldInfo = (~)Word32
type AttrTransferType OutputMessageBytesSentFieldInfo = Word32
type AttrGetType OutputMessageBytesSentFieldInfo = Word32
type AttrLabel OutputMessageBytesSentFieldInfo = "bytes_sent"
type AttrOrigin OutputMessageBytesSentFieldInfo = OutputMessage
attrGet = getOutputMessageBytesSent
attrSet = setOutputMessageBytesSent
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
outputMessage_bytesSent :: AttrLabelProxy "bytesSent"
outputMessage_bytesSent = AttrLabelProxy
#endif
getOutputMessageNumControlMessages :: MonadIO m => OutputMessage -> m Word32
getOutputMessageNumControlMessages :: OutputMessage -> m Word32
getOutputMessageNumControlMessages s :: OutputMessage
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO Word32) -> IO Word32)
-> (Ptr OutputMessage -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setOutputMessageNumControlMessages :: MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageNumControlMessages :: OutputMessage -> Word32 -> m ()
setOutputMessageNumControlMessages s :: OutputMessage
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OutputMessage -> (Ptr OutputMessage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputMessage
s ((Ptr OutputMessage -> IO ()) -> IO ())
-> (Ptr OutputMessage -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputMessage
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputMessage
ptr Ptr OutputMessage -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data OutputMessageNumControlMessagesFieldInfo
instance AttrInfo OutputMessageNumControlMessagesFieldInfo where
type AttrBaseTypeConstraint OutputMessageNumControlMessagesFieldInfo = (~) OutputMessage
type AttrAllowedOps OutputMessageNumControlMessagesFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OutputMessageNumControlMessagesFieldInfo = (~) Word32
type AttrTransferTypeConstraint OutputMessageNumControlMessagesFieldInfo = (~)Word32
type AttrTransferType OutputMessageNumControlMessagesFieldInfo = Word32
type AttrGetType OutputMessageNumControlMessagesFieldInfo = Word32
type AttrLabel OutputMessageNumControlMessagesFieldInfo = "num_control_messages"
type AttrOrigin OutputMessageNumControlMessagesFieldInfo = OutputMessage
attrGet = getOutputMessageNumControlMessages
attrSet = setOutputMessageNumControlMessages
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
outputMessage_numControlMessages :: AttrLabelProxy "numControlMessages"
outputMessage_numControlMessages = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList OutputMessage
type instance O.AttributeList OutputMessage = OutputMessageAttributeList
type OutputMessageAttributeList = ('[ '("address", OutputMessageAddressFieldInfo), '("vectors", OutputMessageVectorsFieldInfo), '("numVectors", OutputMessageNumVectorsFieldInfo), '("bytesSent", OutputMessageBytesSentFieldInfo), '("numControlMessages", OutputMessageNumControlMessagesFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveOutputMessageMethod (t :: Symbol) (o :: *) :: * where
ResolveOutputMessageMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveOutputMessageMethod t OutputMessage, O.MethodInfo info OutputMessage p) => OL.IsLabel t (OutputMessage -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif