{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.EventProperty
    ( 
    EventProperty(..)                       ,
    newZeroEventProperty                    ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveEventPropertyMethod              ,
#endif
 
#if defined(ENABLE_OVERLOADING)
    eventProperty_atom                      ,
#endif
    getEventPropertyAtom                    ,
#if defined(ENABLE_OVERLOADING)
    eventProperty_sendEvent                 ,
#endif
    getEventPropertySendEvent               ,
    setEventPropertySendEvent               ,
#if defined(ENABLE_OVERLOADING)
    eventProperty_state                     ,
#endif
    getEventPropertyState                   ,
    setEventPropertyState                   ,
#if defined(ENABLE_OVERLOADING)
    eventProperty_time                      ,
#endif
    getEventPropertyTime                    ,
    setEventPropertyTime                    ,
#if defined(ENABLE_OVERLOADING)
    eventProperty_type                      ,
#endif
    getEventPropertyType                    ,
    setEventPropertyType                    ,
    clearEventPropertyWindow                ,
#if defined(ENABLE_OVERLOADING)
    eventProperty_window                    ,
#endif
    getEventPropertyWindow                  ,
    setEventPropertyWindow                  ,
    ) 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.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.EventConfigure as Gdk.EventConfigure
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.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
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
#endif
newtype EventProperty = EventProperty (SP.ManagedPtr EventProperty)
    deriving (EventProperty -> EventProperty -> Bool
(EventProperty -> EventProperty -> Bool)
-> (EventProperty -> EventProperty -> Bool) -> Eq EventProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventProperty -> EventProperty -> Bool
== :: EventProperty -> EventProperty -> Bool
$c/= :: EventProperty -> EventProperty -> Bool
/= :: EventProperty -> EventProperty -> Bool
Eq)
instance SP.ManagedPtrNewtype EventProperty where
    toManagedPtr :: EventProperty -> ManagedPtr EventProperty
toManagedPtr (EventProperty ManagedPtr EventProperty
p) = ManagedPtr EventProperty
p
instance BoxedPtr EventProperty where
    boxedPtrCopy :: EventProperty -> IO EventProperty
boxedPtrCopy = \EventProperty
p -> EventProperty
-> (Ptr EventProperty -> IO EventProperty) -> IO EventProperty
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EventProperty
p (Int -> Ptr EventProperty -> IO (Ptr EventProperty)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
40 (Ptr EventProperty -> IO (Ptr EventProperty))
-> (Ptr EventProperty -> IO EventProperty)
-> Ptr EventProperty
-> IO EventProperty
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventProperty -> EventProperty)
-> Ptr EventProperty -> IO EventProperty
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr EventProperty -> EventProperty
EventProperty)
    boxedPtrFree :: EventProperty -> IO ()
boxedPtrFree = \EventProperty
x -> EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr EventProperty
x Ptr EventProperty -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr EventProperty where
    boxedPtrCalloc :: IO (Ptr EventProperty)
boxedPtrCalloc = Int -> IO (Ptr EventProperty)
forall a. Int -> IO (Ptr a)
callocBytes Int
40
newZeroEventProperty :: MonadIO m => m EventProperty
newZeroEventProperty :: forall (m :: * -> *). MonadIO m => m EventProperty
newZeroEventProperty = IO EventProperty -> m EventProperty
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventProperty -> m EventProperty)
-> IO EventProperty -> m EventProperty
forall a b. (a -> b) -> a -> b
$ IO (Ptr EventProperty)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr EventProperty)
-> (Ptr EventProperty -> IO EventProperty) -> IO EventProperty
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventProperty -> EventProperty)
-> Ptr EventProperty -> IO EventProperty
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventProperty -> EventProperty
EventProperty
instance tag ~ 'AttrSet => Constructible EventProperty tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr EventProperty -> EventProperty)
-> [AttrOp EventProperty tag] -> m EventProperty
new ManagedPtr EventProperty -> EventProperty
_ [AttrOp EventProperty tag]
attrs = do
        EventProperty
o <- m EventProperty
forall (m :: * -> *). MonadIO m => m EventProperty
newZeroEventProperty
        EventProperty -> [AttrOp EventProperty 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set EventProperty
o [AttrOp EventProperty tag]
[AttrOp EventProperty 'AttrSet]
attrs
        EventProperty -> m EventProperty
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return EventProperty
o
getEventPropertyType :: MonadIO m => EventProperty -> m Gdk.Enums.EventType
getEventPropertyType :: forall (m :: * -> *). MonadIO m => EventProperty -> m EventType
getEventPropertyType EventProperty
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
$ EventProperty
-> (Ptr EventProperty -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO EventType) -> IO EventType)
-> (Ptr EventProperty -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> 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'
setEventPropertyType :: MonadIO m => EventProperty -> Gdk.Enums.EventType -> m ()
setEventPropertyType :: forall (m :: * -> *).
MonadIO m =>
EventProperty -> EventType -> m ()
setEventPropertyType EventProperty
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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
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 EventProperty
ptr Ptr EventProperty -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CInt
val' :: CInt)
#if defined(ENABLE_OVERLOADING)
data EventPropertyTypeFieldInfo
instance AttrInfo EventPropertyTypeFieldInfo where
    type AttrBaseTypeConstraint EventPropertyTypeFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPropertyTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrTransferTypeConstraint EventPropertyTypeFieldInfo = (~)Gdk.Enums.EventType
    type AttrTransferType EventPropertyTypeFieldInfo = Gdk.Enums.EventType
    type AttrGetType EventPropertyTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventPropertyTypeFieldInfo = "type"
    type AttrOrigin EventPropertyTypeFieldInfo = EventProperty
    attrGet = getEventPropertyType
    attrSet = setEventPropertyType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventProperty.type"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventProperty.html#g:attr:type"
        })
eventProperty_type :: AttrLabelProxy "type"
eventProperty_type = AttrLabelProxy
#endif
getEventPropertyWindow :: MonadIO m => EventProperty -> m (Maybe Gdk.Window.Window)
getEventPropertyWindow :: forall (m :: * -> *).
MonadIO m =>
EventProperty -> m (Maybe Window)
getEventPropertyWindow EventProperty
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
$ EventProperty
-> (Ptr EventProperty -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventProperty -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> 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
setEventPropertyWindow :: MonadIO m => EventProperty -> Ptr Gdk.Window.Window -> m ()
setEventPropertyWindow :: forall (m :: * -> *).
MonadIO m =>
EventProperty -> Ptr Window -> m ()
setEventPropertyWindow EventProperty
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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr Window
val :: Ptr Gdk.Window.Window)
clearEventPropertyWindow :: MonadIO m => EventProperty -> m ()
clearEventPropertyWindow :: forall (m :: * -> *). MonadIO m => EventProperty -> m ()
clearEventPropertyWindow EventProperty
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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> 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 EventPropertyWindowFieldInfo
instance AttrInfo EventPropertyWindowFieldInfo where
    type AttrBaseTypeConstraint EventPropertyWindowFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventPropertyWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventPropertyWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventPropertyWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventPropertyWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventPropertyWindowFieldInfo = "window"
    type AttrOrigin EventPropertyWindowFieldInfo = EventProperty
    attrGet = getEventPropertyWindow
    attrSet = setEventPropertyWindow
    attrConstruct = undefined
    attrClear = clearEventPropertyWindow
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventProperty.window"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventProperty.html#g:attr:window"
        })
eventProperty_window :: AttrLabelProxy "window"
eventProperty_window = AttrLabelProxy
#endif
getEventPropertySendEvent :: MonadIO m => EventProperty -> m Int8
getEventPropertySendEvent :: forall (m :: * -> *). MonadIO m => EventProperty -> m Int8
getEventPropertySendEvent EventProperty
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
$ EventProperty -> (Ptr EventProperty -> IO Int8) -> IO Int8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO Int8) -> IO Int8)
-> (Ptr EventProperty -> IO Int8) -> IO Int8
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    Int8
val <- Ptr Int8 -> IO Int8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> 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
setEventPropertySendEvent :: MonadIO m => EventProperty -> Int8 -> m ()
setEventPropertySendEvent :: forall (m :: * -> *). MonadIO m => EventProperty -> Int8 -> m ()
setEventPropertySendEvent EventProperty
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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    Ptr Int8 -> Int8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int8
val :: Int8)
#if defined(ENABLE_OVERLOADING)
data EventPropertySendEventFieldInfo
instance AttrInfo EventPropertySendEventFieldInfo where
    type AttrBaseTypeConstraint EventPropertySendEventFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertySendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPropertySendEventFieldInfo = (~) Int8
    type AttrTransferTypeConstraint EventPropertySendEventFieldInfo = (~)Int8
    type AttrTransferType EventPropertySendEventFieldInfo = Int8
    type AttrGetType EventPropertySendEventFieldInfo = Int8
    type AttrLabel EventPropertySendEventFieldInfo = "send_event"
    type AttrOrigin EventPropertySendEventFieldInfo = EventProperty
    attrGet = getEventPropertySendEvent
    attrSet = setEventPropertySendEvent
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventProperty.sendEvent"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventProperty.html#g:attr:sendEvent"
        })
eventProperty_sendEvent :: AttrLabelProxy "sendEvent"
eventProperty_sendEvent = AttrLabelProxy
#endif
getEventPropertyAtom :: MonadIO m => EventProperty -> m Gdk.Atom.Atom
getEventPropertyAtom :: forall (m :: * -> *). MonadIO m => EventProperty -> m Atom
getEventPropertyAtom EventProperty
s = IO Atom -> m Atom
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Atom -> m Atom) -> IO Atom -> m Atom
forall a b. (a -> b) -> a -> b
$ EventProperty -> (Ptr EventProperty -> IO Atom) -> IO Atom
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO Atom) -> IO Atom)
-> (Ptr EventProperty -> IO Atom) -> IO Atom
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    let val :: Ptr Atom
val = Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr Atom
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: (Ptr Gdk.Atom.Atom)
    Atom
val' <- ((ManagedPtr Atom -> Atom) -> Ptr Atom -> IO Atom
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Atom -> Atom
Gdk.Atom.Atom) Ptr Atom
val
    Atom -> IO Atom
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Atom
val'
#if defined(ENABLE_OVERLOADING)
data EventPropertyAtomFieldInfo
instance AttrInfo EventPropertyAtomFieldInfo where
    type AttrBaseTypeConstraint EventPropertyAtomFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyAtomFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventPropertyAtomFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrTransferTypeConstraint EventPropertyAtomFieldInfo = (~)(Ptr Gdk.Atom.Atom)
    type AttrTransferType EventPropertyAtomFieldInfo = (Ptr Gdk.Atom.Atom)
    type AttrGetType EventPropertyAtomFieldInfo = Gdk.Atom.Atom
    type AttrLabel EventPropertyAtomFieldInfo = "atom"
    type AttrOrigin EventPropertyAtomFieldInfo = EventProperty
    attrGet = getEventPropertyAtom
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventProperty.atom"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventProperty.html#g:attr:atom"
        })
eventProperty_atom :: AttrLabelProxy "atom"
eventProperty_atom = AttrLabelProxy
#endif
getEventPropertyTime :: MonadIO m => EventProperty -> m Word32
getEventPropertyTime :: forall (m :: * -> *). MonadIO m => EventProperty -> m Word32
getEventPropertyTime EventProperty
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
$ EventProperty -> (Ptr EventProperty -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO Word32) -> IO Word32)
-> (Ptr EventProperty -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setEventPropertyTime :: MonadIO m => EventProperty -> Word32 -> m ()
setEventPropertyTime :: forall (m :: * -> *). MonadIO m => EventProperty -> Word32 -> m ()
setEventPropertyTime EventProperty
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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data EventPropertyTimeFieldInfo
instance AttrInfo EventPropertyTimeFieldInfo where
    type AttrBaseTypeConstraint EventPropertyTimeFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPropertyTimeFieldInfo = (~) Word32
    type AttrTransferTypeConstraint EventPropertyTimeFieldInfo = (~)Word32
    type AttrTransferType EventPropertyTimeFieldInfo = Word32
    type AttrGetType EventPropertyTimeFieldInfo = Word32
    type AttrLabel EventPropertyTimeFieldInfo = "time"
    type AttrOrigin EventPropertyTimeFieldInfo = EventProperty
    attrGet = getEventPropertyTime
    attrSet = setEventPropertyTime
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventProperty.time"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventProperty.html#g:attr:time"
        })
eventProperty_time :: AttrLabelProxy "time"
eventProperty_time = AttrLabelProxy
#endif
getEventPropertyState :: MonadIO m => EventProperty -> m Gdk.Enums.PropertyState
getEventPropertyState :: forall (m :: * -> *). MonadIO m => EventProperty -> m PropertyState
getEventPropertyState EventProperty
s = IO PropertyState -> m PropertyState
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyState -> m PropertyState)
-> IO PropertyState -> m PropertyState
forall a b. (a -> b) -> a -> b
$ EventProperty
-> (Ptr EventProperty -> IO PropertyState) -> IO PropertyState
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO PropertyState) -> IO PropertyState)
-> (Ptr EventProperty -> IO PropertyState) -> IO PropertyState
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36) :: IO CUInt
    let val' :: PropertyState
val' = (Int -> PropertyState
forall a. Enum a => Int -> a
toEnum (Int -> PropertyState) -> (CUInt -> Int) -> CUInt -> PropertyState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    PropertyState -> IO PropertyState
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PropertyState
val'
setEventPropertyState :: MonadIO m => EventProperty -> Gdk.Enums.PropertyState -> m ()
setEventPropertyState :: forall (m :: * -> *).
MonadIO m =>
EventProperty -> PropertyState -> m ()
setEventPropertyState EventProperty
s PropertyState
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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventProperty
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PropertyState -> Int) -> PropertyState -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PropertyState -> Int
forall a. Enum a => a -> Int
fromEnum) PropertyState
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data EventPropertyStateFieldInfo
instance AttrInfo EventPropertyStateFieldInfo where
    type AttrBaseTypeConstraint EventPropertyStateFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyStateFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPropertyStateFieldInfo = (~) Gdk.Enums.PropertyState
    type AttrTransferTypeConstraint EventPropertyStateFieldInfo = (~)Gdk.Enums.PropertyState
    type AttrTransferType EventPropertyStateFieldInfo = Gdk.Enums.PropertyState
    type AttrGetType EventPropertyStateFieldInfo = Gdk.Enums.PropertyState
    type AttrLabel EventPropertyStateFieldInfo = "state"
    type AttrOrigin EventPropertyStateFieldInfo = EventProperty
    attrGet = getEventPropertyState
    attrSet = setEventPropertyState
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventProperty.state"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventProperty.html#g:attr:state"
        })
eventProperty_state :: AttrLabelProxy "state"
eventProperty_state = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventProperty
type instance O.AttributeList EventProperty = EventPropertyAttributeList
type EventPropertyAttributeList = ('[ '("type", EventPropertyTypeFieldInfo), '("window", EventPropertyWindowFieldInfo), '("sendEvent", EventPropertySendEventFieldInfo), '("atom", EventPropertyAtomFieldInfo), '("time", EventPropertyTimeFieldInfo), '("state", EventPropertyStateFieldInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveEventPropertyMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveEventPropertyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventPropertyMethod t EventProperty, O.OverloadedMethod info EventProperty p) => OL.IsLabel t (EventProperty -> 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 ~ ResolveEventPropertyMethod t EventProperty, O.OverloadedMethod info EventProperty p, R.HasField t EventProperty p) => R.HasField t EventProperty p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveEventPropertyMethod t EventProperty, O.OverloadedMethodInfo info EventProperty) => OL.IsLabel t (O.MethodProxy info EventProperty) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif