{-# 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 ,
#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.SocketConnectable as Gio.SocketConnectable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddressEnumerator as Gio.SocketAddressEnumerator
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector
#else
import {-# SOURCE #-} qualified GI.Gio.Objects.SocketAddress as Gio.SocketAddress
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector
#endif
newtype OutputMessage = OutputMessage (SP.ManagedPtr OutputMessage)
deriving (OutputMessage -> OutputMessage -> Bool
(OutputMessage -> OutputMessage -> Bool)
-> (OutputMessage -> OutputMessage -> Bool) -> Eq OutputMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputMessage -> OutputMessage -> Bool
== :: OutputMessage -> OutputMessage -> Bool
$c/= :: OutputMessage -> OutputMessage -> Bool
/= :: OutputMessage -> OutputMessage -> Bool
Eq)
instance SP.ManagedPtrNewtype OutputMessage where
toManagedPtr :: OutputMessage -> ManagedPtr OutputMessage
toManagedPtr (OutputMessage ManagedPtr OutputMessage
p) = ManagedPtr OutputMessage
p
instance BoxedPtr OutputMessage where
boxedPtrCopy :: OutputMessage -> IO OutputMessage
boxedPtrCopy = \OutputMessage
p -> OutputMessage
-> (Ptr OutputMessage -> IO OutputMessage) -> IO OutputMessage
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr OutputMessage
p (Int -> Ptr OutputMessage -> IO (Ptr OutputMessage)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
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, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr OutputMessage -> OutputMessage
OutputMessage)
boxedPtrFree :: OutputMessage -> IO ()
boxedPtrFree = \OutputMessage
x -> OutputMessage -> (Ptr OutputMessage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr OutputMessage
x Ptr OutputMessage -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr OutputMessage where
boxedPtrCalloc :: IO (Ptr OutputMessage)
boxedPtrCalloc = Int -> IO (Ptr OutputMessage)
forall a. Int -> IO (Ptr a)
callocBytes Int
40
newZeroOutputMessage :: MonadIO m => m OutputMessage
newZeroOutputMessage :: forall (m :: * -> *). MonadIO m => m OutputMessage
newZeroOutputMessage = IO OutputMessage -> m OutputMessage
forall a. IO a -> m a
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. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr OutputMessage)
-> (Ptr OutputMessage -> IO OutputMessage) -> IO OutputMessage
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr OutputMessage -> OutputMessage)
-> Ptr OutputMessage -> IO OutputMessage
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr OutputMessage -> OutputMessage
OutputMessage
instance tag ~ 'AttrSet => Constructible OutputMessage tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr OutputMessage -> OutputMessage)
-> [AttrOp OutputMessage tag] -> m OutputMessage
new ManagedPtr OutputMessage -> OutputMessage
_ [AttrOp OutputMessage tag]
attrs = do
o <- m OutputMessage
forall (m :: * -> *). MonadIO m => m OutputMessage
newZeroOutputMessage
GI.Attributes.set o attrs
return o
getOutputMessageAddress :: MonadIO m => OutputMessage -> m (Maybe Gio.SocketAddress.SocketAddress)
getOutputMessageAddress :: forall (m :: * -> *).
MonadIO m =>
OutputMessage -> m (Maybe SocketAddress)
getOutputMessageAddress OutputMessage
s = IO (Maybe SocketAddress) -> m (Maybe SocketAddress)
forall a. IO a -> m a
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 OutputMessage
ptr -> do
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` Int
0) :: IO (Ptr Gio.SocketAddress.SocketAddress)
result <- SP.convertIfNonNull val $ \Ptr SocketAddress
val' -> do
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'
return val''
return result
setOutputMessageAddress :: MonadIO m => OutputMessage -> Ptr Gio.SocketAddress.SocketAddress -> m ()
setOutputMessageAddress :: forall (m :: * -> *).
MonadIO m =>
OutputMessage -> Ptr SocketAddress -> m ()
setOutputMessageAddress OutputMessage
s Ptr SocketAddress
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
0) (Ptr SocketAddress
val :: Ptr Gio.SocketAddress.SocketAddress)
clearOutputMessageAddress :: MonadIO m => OutputMessage -> m ()
clearOutputMessageAddress :: forall (m :: * -> *). MonadIO m => OutputMessage -> m ()
clearOutputMessageAddress OutputMessage
s = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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 :: forall o.
AttrBaseTypeConstraint OutputMessageAddressFieldInfo o =>
o -> IO (AttrGetType OutputMessageAddressFieldInfo)
attrGet = o -> IO (AttrGetType OutputMessageAddressFieldInfo)
OutputMessage -> IO (Maybe SocketAddress)
forall (m :: * -> *).
MonadIO m =>
OutputMessage -> m (Maybe SocketAddress)
getOutputMessageAddress
attrSet :: forall o b.
(AttrBaseTypeConstraint OutputMessageAddressFieldInfo o,
AttrSetTypeConstraint OutputMessageAddressFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
OutputMessage -> Ptr SocketAddress -> IO ()
forall (m :: * -> *).
MonadIO m =>
OutputMessage -> Ptr SocketAddress -> m ()
setOutputMessageAddress
attrConstruct :: forall o b.
(AttrBaseTypeConstraint OutputMessageAddressFieldInfo o,
AttrSetTypeConstraint OutputMessageAddressFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint OutputMessageAddressFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
OutputMessage -> IO ()
forall (m :: * -> *). MonadIO m => OutputMessage -> m ()
clearOutputMessageAddress
attrTransfer :: forall o b.
(AttrBaseTypeConstraint OutputMessageAddressFieldInfo o,
AttrTransferTypeConstraint OutputMessageAddressFieldInfo b) =>
Proxy o -> b -> IO (AttrTransferType OutputMessageAddressFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.OutputMessage.address"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-OutputMessage.html#g:attr:address"
})
outputMessage_address :: AttrLabelProxy "address"
outputMessage_address :: AttrLabelProxy "address"
outputMessage_address = AttrLabelProxy "address"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
getOutputMessageVectors :: MonadIO m => OutputMessage -> m (Maybe Gio.OutputVector.OutputVector)
getOutputMessageVectors :: forall (m :: * -> *).
MonadIO m =>
OutputMessage -> m (Maybe OutputVector)
getOutputMessageVectors OutputMessage
s = IO (Maybe OutputVector) -> m (Maybe OutputVector)
forall a. IO a -> m a
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 OutputMessage
ptr -> do
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` Int
8) :: IO (Ptr Gio.OutputVector.OutputVector)
result <- SP.convertIfNonNull val $ \Ptr OutputVector
val' -> do
val'' <- ((ManagedPtr OutputVector -> OutputVector)
-> Ptr OutputVector -> IO OutputVector
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr OutputVector -> OutputVector
Gio.OutputVector.OutputVector) Ptr OutputVector
val'
return val''
return result
setOutputMessageVectors :: MonadIO m => OutputMessage -> Ptr Gio.OutputVector.OutputVector -> m ()
setOutputMessageVectors :: forall (m :: * -> *).
MonadIO m =>
OutputMessage -> Ptr OutputVector -> m ()
setOutputMessageVectors OutputMessage
s Ptr OutputVector
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
8) (Ptr OutputVector
val :: Ptr Gio.OutputVector.OutputVector)
clearOutputMessageVectors :: MonadIO m => OutputMessage -> m ()
clearOutputMessageVectors :: forall (m :: * -> *). MonadIO m => OutputMessage -> m ()
clearOutputMessageVectors OutputMessage
s = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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 :: forall o.
AttrBaseTypeConstraint OutputMessageVectorsFieldInfo o =>
o -> IO (AttrGetType OutputMessageVectorsFieldInfo)
attrGet = o -> IO (AttrGetType OutputMessageVectorsFieldInfo)
OutputMessage -> IO (Maybe OutputVector)
forall (m :: * -> *).
MonadIO m =>
OutputMessage -> m (Maybe OutputVector)
getOutputMessageVectors
attrSet :: forall o b.
(AttrBaseTypeConstraint OutputMessageVectorsFieldInfo o,
AttrSetTypeConstraint OutputMessageVectorsFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
OutputMessage -> Ptr OutputVector -> IO ()
forall (m :: * -> *).
MonadIO m =>
OutputMessage -> Ptr OutputVector -> m ()
setOutputMessageVectors
attrConstruct :: forall o b.
(AttrBaseTypeConstraint OutputMessageVectorsFieldInfo o,
AttrSetTypeConstraint OutputMessageVectorsFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint OutputMessageVectorsFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
OutputMessage -> IO ()
forall (m :: * -> *). MonadIO m => OutputMessage -> m ()
clearOutputMessageVectors
attrTransfer :: forall o b.
(AttrBaseTypeConstraint OutputMessageVectorsFieldInfo o,
AttrTransferTypeConstraint OutputMessageVectorsFieldInfo b) =>
Proxy o -> b -> IO (AttrTransferType OutputMessageVectorsFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.OutputMessage.vectors"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-OutputMessage.html#g:attr:vectors"
})
outputMessage_vectors :: AttrLabelProxy "vectors"
outputMessage_vectors :: AttrLabelProxy "vectors"
outputMessage_vectors = AttrLabelProxy "vectors"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
getOutputMessageNumVectors :: MonadIO m => OutputMessage -> m Word32
getOutputMessageNumVectors :: forall (m :: * -> *). MonadIO m => OutputMessage -> m Word32
getOutputMessageNumVectors OutputMessage
s = IO Word32 -> m Word32
forall a. IO a -> m a
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 OutputMessage
ptr -> do
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` Int
16) :: IO Word32
return val
setOutputMessageNumVectors :: MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageNumVectors :: forall (m :: * -> *). MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageNumVectors OutputMessage
s Word32
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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 :: forall o.
AttrBaseTypeConstraint OutputMessageNumVectorsFieldInfo o =>
o -> IO (AttrGetType OutputMessageNumVectorsFieldInfo)
attrGet = o -> IO (AttrGetType OutputMessageNumVectorsFieldInfo)
OutputMessage -> IO Word32
forall (m :: * -> *). MonadIO m => OutputMessage -> m Word32
getOutputMessageNumVectors
attrSet :: forall o b.
(AttrBaseTypeConstraint OutputMessageNumVectorsFieldInfo o,
AttrSetTypeConstraint OutputMessageNumVectorsFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
OutputMessage -> Word32 -> IO ()
forall (m :: * -> *). MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageNumVectors
attrConstruct :: forall o b.
(AttrBaseTypeConstraint OutputMessageNumVectorsFieldInfo o,
AttrSetTypeConstraint OutputMessageNumVectorsFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint OutputMessageNumVectorsFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint OutputMessageNumVectorsFieldInfo o,
AttrTransferTypeConstraint OutputMessageNumVectorsFieldInfo b) =>
Proxy o
-> b -> IO (AttrTransferType OutputMessageNumVectorsFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.OutputMessage.numVectors"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-OutputMessage.html#g:attr:numVectors"
})
outputMessage_numVectors :: AttrLabelProxy "numVectors"
outputMessage_numVectors :: AttrLabelProxy "numVectors"
outputMessage_numVectors = AttrLabelProxy "numVectors"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
getOutputMessageBytesSent :: MonadIO m => OutputMessage -> m Word32
getOutputMessageBytesSent :: forall (m :: * -> *). MonadIO m => OutputMessage -> m Word32
getOutputMessageBytesSent OutputMessage
s = IO Word32 -> m Word32
forall a. IO a -> m a
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 OutputMessage
ptr -> do
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` Int
20) :: IO Word32
return val
setOutputMessageBytesSent :: MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageBytesSent :: forall (m :: * -> *). MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageBytesSent OutputMessage
s Word32
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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 :: forall o.
AttrBaseTypeConstraint OutputMessageBytesSentFieldInfo o =>
o -> IO (AttrGetType OutputMessageBytesSentFieldInfo)
attrGet = o -> IO (AttrGetType OutputMessageBytesSentFieldInfo)
OutputMessage -> IO Word32
forall (m :: * -> *). MonadIO m => OutputMessage -> m Word32
getOutputMessageBytesSent
attrSet :: forall o b.
(AttrBaseTypeConstraint OutputMessageBytesSentFieldInfo o,
AttrSetTypeConstraint OutputMessageBytesSentFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
OutputMessage -> Word32 -> IO ()
forall (m :: * -> *). MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageBytesSent
attrConstruct :: forall o b.
(AttrBaseTypeConstraint OutputMessageBytesSentFieldInfo o,
AttrSetTypeConstraint OutputMessageBytesSentFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint OutputMessageBytesSentFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint OutputMessageBytesSentFieldInfo o,
AttrTransferTypeConstraint OutputMessageBytesSentFieldInfo b) =>
Proxy o
-> b -> IO (AttrTransferType OutputMessageBytesSentFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.OutputMessage.bytesSent"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-OutputMessage.html#g:attr:bytesSent"
})
outputMessage_bytesSent :: AttrLabelProxy "bytesSent"
outputMessage_bytesSent :: AttrLabelProxy "bytesSent"
outputMessage_bytesSent = AttrLabelProxy "bytesSent"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
getOutputMessageNumControlMessages :: MonadIO m => OutputMessage -> m Word32
getOutputMessageNumControlMessages :: forall (m :: * -> *). MonadIO m => OutputMessage -> m Word32
getOutputMessageNumControlMessages OutputMessage
s = IO Word32 -> m Word32
forall a. IO a -> m a
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 OutputMessage
ptr -> do
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` Int
32) :: IO Word32
return val
setOutputMessageNumControlMessages :: MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageNumControlMessages :: forall (m :: * -> *). MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageNumControlMessages OutputMessage
s Word32
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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 :: forall o.
AttrBaseTypeConstraint
OutputMessageNumControlMessagesFieldInfo o =>
o -> IO (AttrGetType OutputMessageNumControlMessagesFieldInfo)
attrGet = o -> IO (AttrGetType OutputMessageNumControlMessagesFieldInfo)
OutputMessage -> IO Word32
forall (m :: * -> *). MonadIO m => OutputMessage -> m Word32
getOutputMessageNumControlMessages
attrSet :: forall o b.
(AttrBaseTypeConstraint OutputMessageNumControlMessagesFieldInfo o,
AttrSetTypeConstraint
OutputMessageNumControlMessagesFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
OutputMessage -> Word32 -> IO ()
forall (m :: * -> *). MonadIO m => OutputMessage -> Word32 -> m ()
setOutputMessageNumControlMessages
attrConstruct :: forall o b.
(AttrBaseTypeConstraint OutputMessageNumControlMessagesFieldInfo o,
AttrSetTypeConstraint
OutputMessageNumControlMessagesFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint
OutputMessageNumControlMessagesFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint OutputMessageNumControlMessagesFieldInfo o,
AttrTransferTypeConstraint
OutputMessageNumControlMessagesFieldInfo b) =>
Proxy o
-> b
-> IO (AttrTransferType OutputMessageNumControlMessagesFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.OutputMessage.numControlMessages"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-OutputMessage.html#g:attr:numControlMessages"
})
outputMessage_numControlMessages :: AttrLabelProxy "numControlMessages"
outputMessage_numControlMessages :: AttrLabelProxy "numControlMessages"
outputMessage_numControlMessages = AttrLabelProxy "numControlMessages"
forall (a :: Symbol). AttrLabelProxy a
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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveOutputMessageMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveOutputMessageMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveOutputMessageMethod t OutputMessage, O.OverloadedMethod info OutputMessage p) => OL.IsLabel t (OutputMessage -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: OutputMessage -> p
fromLabel = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveOutputMessageMethod t OutputMessage, O.OverloadedMethod info OutputMessage p, R.HasField t OutputMessage p) => R.HasField t OutputMessage p where
getField :: OutputMessage -> p
getField = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#endif
instance (info ~ ResolveOutputMessageMethod t OutputMessage, O.OverloadedMethodInfo info OutputMessage) => OL.IsLabel t (O.MethodProxy info OutputMessage) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: MethodProxy info OutputMessage
fromLabel = MethodProxy info OutputMessage
forall info obj. MethodProxy info obj
O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif