{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Generated when a window size or position has changed.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gdk.Structs.EventConfigure
    ( 

-- * Exported types
    EventConfigure(..)                      ,
    newZeroEventConfigure                   ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveEventConfigureMethod             ,
#endif



 -- * Properties


-- ** height #attr:height#
-- | the new height of the window.

#if defined(ENABLE_OVERLOADING)
    eventConfigure_height                   ,
#endif
    getEventConfigureHeight                 ,
    setEventConfigureHeight                 ,


-- ** sendEvent #attr:sendEvent#
-- | 'P.True' if the event was sent explicitly.

#if defined(ENABLE_OVERLOADING)
    eventConfigure_sendEvent                ,
#endif
    getEventConfigureSendEvent              ,
    setEventConfigureSendEvent              ,


-- ** type #attr:type#
-- | the type of the event ('GI.Gdk.Enums.EventTypeConfigure').

#if defined(ENABLE_OVERLOADING)
    eventConfigure_type                     ,
#endif
    getEventConfigureType                   ,
    setEventConfigureType                   ,


-- ** width #attr:width#
-- | the new width of the window.

#if defined(ENABLE_OVERLOADING)
    eventConfigure_width                    ,
#endif
    getEventConfigureWidth                  ,
    setEventConfigureWidth                  ,


-- ** window #attr:window#
-- | the window which received the event.

    clearEventConfigureWindow               ,
#if defined(ENABLE_OVERLOADING)
    eventConfigure_window                   ,
#endif
    getEventConfigureWindow                 ,
    setEventConfigureWindow                 ,


-- ** x #attr:x#
-- | the new x coordinate of the window, relative to its parent.

#if defined(ENABLE_OVERLOADING)
    eventConfigure_x                        ,
#endif
    getEventConfigureX                      ,
    setEventConfigureX                      ,


-- ** y #attr:y#
-- | the new y coordinate of the window, relative to its parent.

#if defined(ENABLE_OVERLOADING)
    eventConfigure_y                        ,
#endif
    getEventConfigureY                      ,
    setEventConfigureY                      ,




    ) 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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Pattern as Cairo.Pattern
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Callbacks as Gdk.Callbacks
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceManager as Gdk.DeviceManager
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.DragContext as Gdk.DragContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawingContext as Gdk.DrawingContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import {-# SOURCE #-} qualified GI.Gdk.Objects.GLContext as Gdk.GLContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Screen as Gdk.Screen
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Visual as Gdk.Visual
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
import {-# SOURCE #-} qualified GI.Gdk.Structs.Color as Gdk.Color
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventDND as Gdk.EventDND
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadAxis as Gdk.EventPadAxis
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadButton as Gdk.EventPadButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadGroupMode as Gdk.EventPadGroupMode
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSetting as Gdk.EventSetting
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouch as Gdk.EventTouch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadPinch as Gdk.EventTouchpadPinch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadSwipe as Gdk.EventTouchpadSwipe
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import {-# SOURCE #-} qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.WindowAttr as Gdk.WindowAttr
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext

#else
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window

#endif

-- | Memory-managed wrapper type.
newtype EventConfigure = EventConfigure (SP.ManagedPtr EventConfigure)
    deriving (EventConfigure -> EventConfigure -> Bool
(EventConfigure -> EventConfigure -> Bool)
-> (EventConfigure -> EventConfigure -> Bool) -> Eq EventConfigure
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventConfigure -> EventConfigure -> Bool
== :: EventConfigure -> EventConfigure -> Bool
$c/= :: EventConfigure -> EventConfigure -> Bool
/= :: EventConfigure -> EventConfigure -> Bool
Eq)

instance SP.ManagedPtrNewtype EventConfigure where
    toManagedPtr :: EventConfigure -> ManagedPtr EventConfigure
toManagedPtr (EventConfigure ManagedPtr EventConfigure
p) = ManagedPtr EventConfigure
p

instance BoxedPtr EventConfigure where
    boxedPtrCopy :: EventConfigure -> IO EventConfigure
boxedPtrCopy = \EventConfigure
p -> EventConfigure
-> (Ptr EventConfigure -> IO EventConfigure) -> IO EventConfigure
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EventConfigure
p (Int -> Ptr EventConfigure -> IO (Ptr EventConfigure)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
40 (Ptr EventConfigure -> IO (Ptr EventConfigure))
-> (Ptr EventConfigure -> IO EventConfigure)
-> Ptr EventConfigure
-> IO EventConfigure
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventConfigure -> EventConfigure)
-> Ptr EventConfigure -> IO EventConfigure
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr EventConfigure -> EventConfigure
EventConfigure)
    boxedPtrFree :: EventConfigure -> IO ()
boxedPtrFree = \EventConfigure
x -> EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr EventConfigure
x Ptr EventConfigure -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr EventConfigure where
    boxedPtrCalloc :: IO (Ptr EventConfigure)
boxedPtrCalloc = Int -> IO (Ptr EventConfigure)
forall a. Int -> IO (Ptr a)
callocBytes Int
40


-- | Construct a `EventConfigure` struct initialized to zero.
newZeroEventConfigure :: MonadIO m => m EventConfigure
newZeroEventConfigure :: forall (m :: * -> *). MonadIO m => m EventConfigure
newZeroEventConfigure = IO EventConfigure -> m EventConfigure
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventConfigure -> m EventConfigure)
-> IO EventConfigure -> m EventConfigure
forall a b. (a -> b) -> a -> b
$ IO (Ptr EventConfigure)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr EventConfigure)
-> (Ptr EventConfigure -> IO EventConfigure) -> IO EventConfigure
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventConfigure -> EventConfigure)
-> Ptr EventConfigure -> IO EventConfigure
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventConfigure -> EventConfigure
EventConfigure

instance tag ~ 'AttrSet => Constructible EventConfigure tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr EventConfigure -> EventConfigure)
-> [AttrOp EventConfigure tag] -> m EventConfigure
new ManagedPtr EventConfigure -> EventConfigure
_ [AttrOp EventConfigure tag]
attrs = do
        EventConfigure
o <- m EventConfigure
forall (m :: * -> *). MonadIO m => m EventConfigure
newZeroEventConfigure
        EventConfigure -> [AttrOp EventConfigure 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set EventConfigure
o [AttrOp EventConfigure tag]
[AttrOp EventConfigure 'AttrSet]
attrs
        EventConfigure -> m EventConfigure
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return EventConfigure
o


-- | Get the value of the “@type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventConfigure #type
-- @
getEventConfigureType :: MonadIO m => EventConfigure -> m Gdk.Enums.EventType
getEventConfigureType :: forall (m :: * -> *). MonadIO m => EventConfigure -> m EventType
getEventConfigureType EventConfigure
s = IO EventType -> m EventType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventType -> m EventType) -> IO EventType -> m EventType
forall a b. (a -> b) -> a -> b
$ EventConfigure
-> (Ptr EventConfigure -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO EventType) -> IO EventType)
-> (Ptr EventConfigure -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CInt
    let val' :: EventType
val' = (Int -> EventType
forall a. Enum a => Int -> a
toEnum (Int -> EventType) -> (CInt -> Int) -> CInt -> EventType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
val
    EventType -> IO EventType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EventType
val'

-- | Set the value of the “@type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventConfigure [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventConfigureType :: MonadIO m => EventConfigure -> Gdk.Enums.EventType -> m ()
setEventConfigureType :: forall (m :: * -> *).
MonadIO m =>
EventConfigure -> EventType -> m ()
setEventConfigureType EventConfigure
s EventType
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
$ EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO ()) -> IO ())
-> (Ptr EventConfigure -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    let val' :: CInt
val' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EventType -> Int) -> EventType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventType -> Int
forall a. Enum a => a -> Int
fromEnum) EventType
val
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CInt
val' :: CInt)

#if defined(ENABLE_OVERLOADING)
data EventConfigureTypeFieldInfo
instance AttrInfo EventConfigureTypeFieldInfo where
    type AttrBaseTypeConstraint EventConfigureTypeFieldInfo = (~) EventConfigure
    type AttrAllowedOps EventConfigureTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventConfigureTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrTransferTypeConstraint EventConfigureTypeFieldInfo = (~)Gdk.Enums.EventType
    type AttrTransferType EventConfigureTypeFieldInfo = Gdk.Enums.EventType
    type AttrGetType EventConfigureTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventConfigureTypeFieldInfo = "type"
    type AttrOrigin EventConfigureTypeFieldInfo = EventConfigure
    attrGet = getEventConfigureType
    attrSet = setEventConfigureType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventConfigure.type"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventConfigure.html#g:attr:type"
        })

eventConfigure_type :: AttrLabelProxy "type"
eventConfigure_type = AttrLabelProxy

#endif


-- | Get the value of the “@window@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventConfigure #window
-- @
getEventConfigureWindow :: MonadIO m => EventConfigure -> m (Maybe Gdk.Window.Window)
getEventConfigureWindow :: forall (m :: * -> *).
MonadIO m =>
EventConfigure -> m (Maybe Window)
getEventConfigureWindow EventConfigure
s = IO (Maybe Window) -> m (Maybe Window)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ EventConfigure
-> (Ptr EventConfigure -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventConfigure -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr Gdk.Window.Window)
    Maybe Window
result <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Window
val ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr Window
val' -> do
        Window
val'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
val'
        Window -> IO Window
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Window
val''
    Maybe Window -> IO (Maybe Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
result

-- | Set the value of the “@window@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventConfigure [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventConfigureWindow :: MonadIO m => EventConfigure -> Ptr Gdk.Window.Window -> m ()
setEventConfigureWindow :: forall (m :: * -> *).
MonadIO m =>
EventConfigure -> Ptr Window -> m ()
setEventConfigureWindow EventConfigure
s Ptr Window
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
$ EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO ()) -> IO ())
-> (Ptr EventConfigure -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr Window
val :: Ptr Gdk.Window.Window)

-- | Set the value of the “@window@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #window
-- @
clearEventConfigureWindow :: MonadIO m => EventConfigure -> m ()
clearEventConfigureWindow :: forall (m :: * -> *). MonadIO m => EventConfigure -> m ()
clearEventConfigureWindow EventConfigure
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
$ EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO ()) -> IO ())
-> (Ptr EventConfigure -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr Window
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Window.Window)

#if defined(ENABLE_OVERLOADING)
data EventConfigureWindowFieldInfo
instance AttrInfo EventConfigureWindowFieldInfo where
    type AttrBaseTypeConstraint EventConfigureWindowFieldInfo = (~) EventConfigure
    type AttrAllowedOps EventConfigureWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventConfigureWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventConfigureWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventConfigureWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventConfigureWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventConfigureWindowFieldInfo = "window"
    type AttrOrigin EventConfigureWindowFieldInfo = EventConfigure
    attrGet = getEventConfigureWindow
    attrSet = setEventConfigureWindow
    attrConstruct = undefined
    attrClear = clearEventConfigureWindow
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventConfigure.window"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventConfigure.html#g:attr:window"
        })

eventConfigure_window :: AttrLabelProxy "window"
eventConfigure_window = AttrLabelProxy

#endif


-- | Get the value of the “@send_event@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventConfigure #sendEvent
-- @
getEventConfigureSendEvent :: MonadIO m => EventConfigure -> m Int8
getEventConfigureSendEvent :: forall (m :: * -> *). MonadIO m => EventConfigure -> m Int8
getEventConfigureSendEvent EventConfigure
s = IO Int8 -> m Int8
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int8 -> m Int8) -> IO Int8 -> m Int8
forall a b. (a -> b) -> a -> b
$ EventConfigure -> (Ptr EventConfigure -> IO Int8) -> IO Int8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO Int8) -> IO Int8)
-> (Ptr EventConfigure -> IO Int8) -> IO Int8
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Int8
val <- Ptr Int8 -> IO Int8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int8
    Int8 -> IO Int8
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int8
val

-- | Set the value of the “@send_event@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventConfigure [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventConfigureSendEvent :: MonadIO m => EventConfigure -> Int8 -> m ()
setEventConfigureSendEvent :: forall (m :: * -> *). MonadIO m => EventConfigure -> Int8 -> m ()
setEventConfigureSendEvent EventConfigure
s Int8
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
$ EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO ()) -> IO ())
-> (Ptr EventConfigure -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Ptr Int8 -> Int8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int8
val :: Int8)

#if defined(ENABLE_OVERLOADING)
data EventConfigureSendEventFieldInfo
instance AttrInfo EventConfigureSendEventFieldInfo where
    type AttrBaseTypeConstraint EventConfigureSendEventFieldInfo = (~) EventConfigure
    type AttrAllowedOps EventConfigureSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventConfigureSendEventFieldInfo = (~) Int8
    type AttrTransferTypeConstraint EventConfigureSendEventFieldInfo = (~)Int8
    type AttrTransferType EventConfigureSendEventFieldInfo = Int8
    type AttrGetType EventConfigureSendEventFieldInfo = Int8
    type AttrLabel EventConfigureSendEventFieldInfo = "send_event"
    type AttrOrigin EventConfigureSendEventFieldInfo = EventConfigure
    attrGet = getEventConfigureSendEvent
    attrSet = setEventConfigureSendEvent
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventConfigure.sendEvent"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventConfigure.html#g:attr:sendEvent"
        })

eventConfigure_sendEvent :: AttrLabelProxy "sendEvent"
eventConfigure_sendEvent = AttrLabelProxy

#endif


-- | Get the value of the “@x@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventConfigure #x
-- @
getEventConfigureX :: MonadIO m => EventConfigure -> m Int32
getEventConfigureX :: forall (m :: * -> *). MonadIO m => EventConfigure -> m Int32
getEventConfigureX EventConfigure
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ EventConfigure -> (Ptr EventConfigure -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO Int32) -> IO Int32)
-> (Ptr EventConfigure -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@x@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventConfigure [ #x 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventConfigureX :: MonadIO m => EventConfigure -> Int32 -> m ()
setEventConfigureX :: forall (m :: * -> *). MonadIO m => EventConfigure -> Int32 -> m ()
setEventConfigureX EventConfigure
s Int32
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
$ EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO ()) -> IO ())
-> (Ptr EventConfigure -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data EventConfigureXFieldInfo
instance AttrInfo EventConfigureXFieldInfo where
    type AttrBaseTypeConstraint EventConfigureXFieldInfo = (~) EventConfigure
    type AttrAllowedOps EventConfigureXFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventConfigureXFieldInfo = (~) Int32
    type AttrTransferTypeConstraint EventConfigureXFieldInfo = (~)Int32
    type AttrTransferType EventConfigureXFieldInfo = Int32
    type AttrGetType EventConfigureXFieldInfo = Int32
    type AttrLabel EventConfigureXFieldInfo = "x"
    type AttrOrigin EventConfigureXFieldInfo = EventConfigure
    attrGet = getEventConfigureX
    attrSet = setEventConfigureX
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventConfigure.x"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventConfigure.html#g:attr:x"
        })

eventConfigure_x :: AttrLabelProxy "x"
eventConfigure_x = AttrLabelProxy

#endif


-- | Get the value of the “@y@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventConfigure #y
-- @
getEventConfigureY :: MonadIO m => EventConfigure -> m Int32
getEventConfigureY :: forall (m :: * -> *). MonadIO m => EventConfigure -> m Int32
getEventConfigureY EventConfigure
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ EventConfigure -> (Ptr EventConfigure -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO Int32) -> IO Int32)
-> (Ptr EventConfigure -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@y@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventConfigure [ #y 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventConfigureY :: MonadIO m => EventConfigure -> Int32 -> m ()
setEventConfigureY :: forall (m :: * -> *). MonadIO m => EventConfigure -> Int32 -> m ()
setEventConfigureY EventConfigure
s Int32
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
$ EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO ()) -> IO ())
-> (Ptr EventConfigure -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data EventConfigureYFieldInfo
instance AttrInfo EventConfigureYFieldInfo where
    type AttrBaseTypeConstraint EventConfigureYFieldInfo = (~) EventConfigure
    type AttrAllowedOps EventConfigureYFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventConfigureYFieldInfo = (~) Int32
    type AttrTransferTypeConstraint EventConfigureYFieldInfo = (~)Int32
    type AttrTransferType EventConfigureYFieldInfo = Int32
    type AttrGetType EventConfigureYFieldInfo = Int32
    type AttrLabel EventConfigureYFieldInfo = "y"
    type AttrOrigin EventConfigureYFieldInfo = EventConfigure
    attrGet = getEventConfigureY
    attrSet = setEventConfigureY
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventConfigure.y"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventConfigure.html#g:attr:y"
        })

eventConfigure_y :: AttrLabelProxy "y"
eventConfigure_y = AttrLabelProxy

#endif


-- | Get the value of the “@width@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventConfigure #width
-- @
getEventConfigureWidth :: MonadIO m => EventConfigure -> m Int32
getEventConfigureWidth :: forall (m :: * -> *). MonadIO m => EventConfigure -> m Int32
getEventConfigureWidth EventConfigure
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ EventConfigure -> (Ptr EventConfigure -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO Int32) -> IO Int32)
-> (Ptr EventConfigure -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@width@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventConfigure [ #width 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventConfigureWidth :: MonadIO m => EventConfigure -> Int32 -> m ()
setEventConfigureWidth :: forall (m :: * -> *). MonadIO m => EventConfigure -> Int32 -> m ()
setEventConfigureWidth EventConfigure
s Int32
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
$ EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO ()) -> IO ())
-> (Ptr EventConfigure -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data EventConfigureWidthFieldInfo
instance AttrInfo EventConfigureWidthFieldInfo where
    type AttrBaseTypeConstraint EventConfigureWidthFieldInfo = (~) EventConfigure
    type AttrAllowedOps EventConfigureWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventConfigureWidthFieldInfo = (~) Int32
    type AttrTransferTypeConstraint EventConfigureWidthFieldInfo = (~)Int32
    type AttrTransferType EventConfigureWidthFieldInfo = Int32
    type AttrGetType EventConfigureWidthFieldInfo = Int32
    type AttrLabel EventConfigureWidthFieldInfo = "width"
    type AttrOrigin EventConfigureWidthFieldInfo = EventConfigure
    attrGet = getEventConfigureWidth
    attrSet = setEventConfigureWidth
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventConfigure.width"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventConfigure.html#g:attr:width"
        })

eventConfigure_width :: AttrLabelProxy "width"
eventConfigure_width = AttrLabelProxy

#endif


-- | Get the value of the “@height@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventConfigure #height
-- @
getEventConfigureHeight :: MonadIO m => EventConfigure -> m Int32
getEventConfigureHeight :: forall (m :: * -> *). MonadIO m => EventConfigure -> m Int32
getEventConfigureHeight EventConfigure
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ EventConfigure -> (Ptr EventConfigure -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO Int32) -> IO Int32)
-> (Ptr EventConfigure -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@height@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventConfigure [ #height 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventConfigureHeight :: MonadIO m => EventConfigure -> Int32 -> m ()
setEventConfigureHeight :: forall (m :: * -> *). MonadIO m => EventConfigure -> Int32 -> m ()
setEventConfigureHeight EventConfigure
s Int32
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
$ EventConfigure -> (Ptr EventConfigure -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventConfigure
s ((Ptr EventConfigure -> IO ()) -> IO ())
-> (Ptr EventConfigure -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventConfigure
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventConfigure
ptr Ptr EventConfigure -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data EventConfigureHeightFieldInfo
instance AttrInfo EventConfigureHeightFieldInfo where
    type AttrBaseTypeConstraint EventConfigureHeightFieldInfo = (~) EventConfigure
    type AttrAllowedOps EventConfigureHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventConfigureHeightFieldInfo = (~) Int32
    type AttrTransferTypeConstraint EventConfigureHeightFieldInfo = (~)Int32
    type AttrTransferType EventConfigureHeightFieldInfo = Int32
    type AttrGetType EventConfigureHeightFieldInfo = Int32
    type AttrLabel EventConfigureHeightFieldInfo = "height"
    type AttrOrigin EventConfigureHeightFieldInfo = EventConfigure
    attrGet = getEventConfigureHeight
    attrSet = setEventConfigureHeight
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventConfigure.height"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventConfigure.html#g:attr:height"
        })

eventConfigure_height :: AttrLabelProxy "height"
eventConfigure_height = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventConfigure
type instance O.AttributeList EventConfigure = EventConfigureAttributeList
type EventConfigureAttributeList = ('[ '("type", EventConfigureTypeFieldInfo), '("window", EventConfigureWindowFieldInfo), '("sendEvent", EventConfigureSendEventFieldInfo), '("x", EventConfigureXFieldInfo), '("y", EventConfigureYFieldInfo), '("width", EventConfigureWidthFieldInfo), '("height", EventConfigureHeightFieldInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveEventConfigureMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveEventConfigureMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveEventConfigureMethod t EventConfigure, O.OverloadedMethod info EventConfigure p) => OL.IsLabel t (EventConfigure -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveEventConfigureMethod t EventConfigure, O.OverloadedMethod info EventConfigure p, R.HasField t EventConfigure p) => R.HasField t EventConfigure p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveEventConfigureMethod t EventConfigure, O.OverloadedMethodInfo info EventConfigure) => OL.IsLabel t (O.MethodProxy info EventConfigure) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif