{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Generated when a selection is requested or ownership of a selection
-- is taken over by another client application.

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

module GI.Gdk.Structs.EventSelection
    ( 

-- * Exported types
    EventSelection(..)                      ,
    newZeroEventSelection                   ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveEventSelectionMethod             ,
#endif



 -- * Properties


-- ** property #attr:property#
-- | the property in which to place the result of the conversion.

#if defined(ENABLE_OVERLOADING)
    eventSelection_property                 ,
#endif
    getEventSelectionProperty               ,


-- ** requestor #attr:requestor#
-- | the window on which to place /@property@/ or 'P.Nothing' if none.

    clearEventSelectionRequestor            ,
#if defined(ENABLE_OVERLOADING)
    eventSelection_requestor                ,
#endif
    getEventSelectionRequestor              ,
    setEventSelectionRequestor              ,


-- ** selection #attr:selection#
-- | the selection.

#if defined(ENABLE_OVERLOADING)
    eventSelection_selection                ,
#endif
    getEventSelectionSelection              ,


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

#if defined(ENABLE_OVERLOADING)
    eventSelection_sendEvent                ,
#endif
    getEventSelectionSendEvent              ,
    setEventSelectionSendEvent              ,


-- ** target #attr:target#
-- | the target to which the selection should be converted.

#if defined(ENABLE_OVERLOADING)
    eventSelection_target                   ,
#endif
    getEventSelectionTarget                 ,


-- ** time #attr:time#
-- | the time of the event in milliseconds.

#if defined(ENABLE_OVERLOADING)
    eventSelection_time                     ,
#endif
    getEventSelectionTime                   ,
    setEventSelectionTime                   ,


-- ** type #attr:type#
-- | the type of the event ('GI.Gdk.Enums.EventTypeSelectionClear',
--   'GI.Gdk.Enums.EventTypeSelectionNotify' or 'GI.Gdk.Enums.EventTypeSelectionRequest').

#if defined(ENABLE_OVERLOADING)
    eventSelection_type                     ,
#endif
    getEventSelectionType                   ,
    setEventSelectionType                   ,


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

    clearEventSelectionWindow               ,
#if defined(ENABLE_OVERLOADING)
    eventSelection_window                   ,
#endif
    getEventSelectionWindow                 ,
    setEventSelectionWindow                 ,




    ) 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.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.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.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

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

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

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


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

instance tag ~ 'AttrSet => Constructible EventSelection tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr EventSelection -> EventSelection)
-> [AttrOp EventSelection tag] -> m EventSelection
new ManagedPtr EventSelection -> EventSelection
_ [AttrOp EventSelection tag]
attrs = do
        EventSelection
o <- m EventSelection
forall (m :: * -> *). MonadIO m => m EventSelection
newZeroEventSelection
        EventSelection -> [AttrOp EventSelection 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set EventSelection
o [AttrOp EventSelection tag]
[AttrOp EventSelection 'AttrSet]
attrs
        EventSelection -> m EventSelection
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return EventSelection
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' eventSelection #type
-- @
getEventSelectionType :: MonadIO m => EventSelection -> m Gdk.Enums.EventType
getEventSelectionType :: forall (m :: * -> *). MonadIO m => EventSelection -> m EventType
getEventSelectionType EventSelection
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
$ EventSelection
-> (Ptr EventSelection -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO EventType) -> IO EventType)
-> (Ptr EventSelection -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventSelection
ptr Ptr EventSelection -> 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' eventSelection [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventSelectionType :: MonadIO m => EventSelection -> Gdk.Enums.EventType -> m ()
setEventSelectionType :: forall (m :: * -> *).
MonadIO m =>
EventSelection -> EventType -> m ()
setEventSelectionType EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO ()) -> IO ())
-> (Ptr EventSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
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 EventSelection
ptr Ptr EventSelection -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CInt
val' :: CInt)

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

eventSelection_type :: AttrLabelProxy "type"
eventSelection_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' eventSelection #window
-- @
getEventSelectionWindow :: MonadIO m => EventSelection -> m (Maybe Gdk.Window.Window)
getEventSelectionWindow :: forall (m :: * -> *).
MonadIO m =>
EventSelection -> m (Maybe Window)
getEventSelectionWindow EventSelection
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
$ EventSelection
-> (Ptr EventSelection -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventSelection -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventSelection
ptr Ptr EventSelection -> 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' eventSelection [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventSelectionWindow :: MonadIO m => EventSelection -> Ptr Gdk.Window.Window -> m ()
setEventSelectionWindow :: forall (m :: * -> *).
MonadIO m =>
EventSelection -> Ptr Window -> m ()
setEventSelectionWindow EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO ()) -> IO ())
-> (Ptr EventSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventSelection
ptr Ptr EventSelection -> 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
-- @
clearEventSelectionWindow :: MonadIO m => EventSelection -> m ()
clearEventSelectionWindow :: forall (m :: * -> *). MonadIO m => EventSelection -> m ()
clearEventSelectionWindow EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO ()) -> IO ())
-> (Ptr EventSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventSelection
ptr Ptr EventSelection -> 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 EventSelectionWindowFieldInfo
instance AttrInfo EventSelectionWindowFieldInfo where
    type AttrBaseTypeConstraint EventSelectionWindowFieldInfo = (~) EventSelection
    type AttrAllowedOps EventSelectionWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventSelectionWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventSelectionWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventSelectionWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventSelectionWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventSelectionWindowFieldInfo = "window"
    type AttrOrigin EventSelectionWindowFieldInfo = EventSelection
    attrGet = getEventSelectionWindow
    attrSet = setEventSelectionWindow
    attrConstruct = undefined
    attrClear = clearEventSelectionWindow
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventSelection.window"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventSelection.html#g:attr:window"
        })

eventSelection_window :: AttrLabelProxy "window"
eventSelection_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' eventSelection #sendEvent
-- @
getEventSelectionSendEvent :: MonadIO m => EventSelection -> m Int8
getEventSelectionSendEvent :: forall (m :: * -> *). MonadIO m => EventSelection -> m Int8
getEventSelectionSendEvent EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO Int8) -> IO Int8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO Int8) -> IO Int8)
-> (Ptr EventSelection -> IO Int8) -> IO Int8
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    Int8
val <- Ptr Int8 -> IO Int8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventSelection
ptr Ptr EventSelection -> 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' eventSelection [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventSelectionSendEvent :: MonadIO m => EventSelection -> Int8 -> m ()
setEventSelectionSendEvent :: forall (m :: * -> *). MonadIO m => EventSelection -> Int8 -> m ()
setEventSelectionSendEvent EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO ()) -> IO ())
-> (Ptr EventSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    Ptr Int8 -> Int8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventSelection
ptr Ptr EventSelection -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int8
val :: Int8)

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

eventSelection_sendEvent :: AttrLabelProxy "sendEvent"
eventSelection_sendEvent = AttrLabelProxy

#endif


-- | Get the value of the “@selection@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventSelection #selection
-- @
getEventSelectionSelection :: MonadIO m => EventSelection -> m Gdk.Atom.Atom
getEventSelectionSelection :: forall (m :: * -> *). MonadIO m => EventSelection -> m Atom
getEventSelectionSelection EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO Atom) -> IO Atom
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO Atom) -> IO Atom)
-> (Ptr EventSelection -> IO Atom) -> IO Atom
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    let val :: Ptr Atom
val = Ptr EventSelection
ptr Ptr EventSelection -> 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 EventSelectionSelectionFieldInfo
instance AttrInfo EventSelectionSelectionFieldInfo where
    type AttrBaseTypeConstraint EventSelectionSelectionFieldInfo = (~) EventSelection
    type AttrAllowedOps EventSelectionSelectionFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventSelectionSelectionFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrTransferTypeConstraint EventSelectionSelectionFieldInfo = (~)(Ptr Gdk.Atom.Atom)
    type AttrTransferType EventSelectionSelectionFieldInfo = (Ptr Gdk.Atom.Atom)
    type AttrGetType EventSelectionSelectionFieldInfo = Gdk.Atom.Atom
    type AttrLabel EventSelectionSelectionFieldInfo = "selection"
    type AttrOrigin EventSelectionSelectionFieldInfo = EventSelection
    attrGet = getEventSelectionSelection
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventSelection.selection"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventSelection.html#g:attr:selection"
        })

eventSelection_selection :: AttrLabelProxy "selection"
eventSelection_selection = AttrLabelProxy

#endif


-- | Get the value of the “@target@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventSelection #target
-- @
getEventSelectionTarget :: MonadIO m => EventSelection -> m Gdk.Atom.Atom
getEventSelectionTarget :: forall (m :: * -> *). MonadIO m => EventSelection -> m Atom
getEventSelectionTarget EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO Atom) -> IO Atom
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO Atom) -> IO Atom)
-> (Ptr EventSelection -> IO Atom) -> IO Atom
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    let val :: Ptr Atom
val = Ptr EventSelection
ptr Ptr EventSelection -> Int -> Ptr Atom
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: (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 EventSelectionTargetFieldInfo
instance AttrInfo EventSelectionTargetFieldInfo where
    type AttrBaseTypeConstraint EventSelectionTargetFieldInfo = (~) EventSelection
    type AttrAllowedOps EventSelectionTargetFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventSelectionTargetFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrTransferTypeConstraint EventSelectionTargetFieldInfo = (~)(Ptr Gdk.Atom.Atom)
    type AttrTransferType EventSelectionTargetFieldInfo = (Ptr Gdk.Atom.Atom)
    type AttrGetType EventSelectionTargetFieldInfo = Gdk.Atom.Atom
    type AttrLabel EventSelectionTargetFieldInfo = "target"
    type AttrOrigin EventSelectionTargetFieldInfo = EventSelection
    attrGet = getEventSelectionTarget
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventSelection.target"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventSelection.html#g:attr:target"
        })

eventSelection_target :: AttrLabelProxy "target"
eventSelection_target = AttrLabelProxy

#endif


-- | Get the value of the “@property@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventSelection #property
-- @
getEventSelectionProperty :: MonadIO m => EventSelection -> m Gdk.Atom.Atom
getEventSelectionProperty :: forall (m :: * -> *). MonadIO m => EventSelection -> m Atom
getEventSelectionProperty EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO Atom) -> IO Atom
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO Atom) -> IO Atom)
-> (Ptr EventSelection -> IO Atom) -> IO Atom
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    let val :: Ptr Atom
val = Ptr EventSelection
ptr Ptr EventSelection -> Int -> Ptr Atom
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: (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 EventSelectionPropertyFieldInfo
instance AttrInfo EventSelectionPropertyFieldInfo where
    type AttrBaseTypeConstraint EventSelectionPropertyFieldInfo = (~) EventSelection
    type AttrAllowedOps EventSelectionPropertyFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventSelectionPropertyFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrTransferTypeConstraint EventSelectionPropertyFieldInfo = (~)(Ptr Gdk.Atom.Atom)
    type AttrTransferType EventSelectionPropertyFieldInfo = (Ptr Gdk.Atom.Atom)
    type AttrGetType EventSelectionPropertyFieldInfo = Gdk.Atom.Atom
    type AttrLabel EventSelectionPropertyFieldInfo = "property"
    type AttrOrigin EventSelectionPropertyFieldInfo = EventSelection
    attrGet = getEventSelectionProperty
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventSelection.property"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventSelection.html#g:attr:property"
        })

eventSelection_property :: AttrLabelProxy "property"
eventSelection_property = AttrLabelProxy

#endif


-- | Get the value of the “@time@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventSelection #time
-- @
getEventSelectionTime :: MonadIO m => EventSelection -> m Word32
getEventSelectionTime :: forall (m :: * -> *). MonadIO m => EventSelection -> m Word32
getEventSelectionTime EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO Word32) -> IO Word32)
-> (Ptr EventSelection -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventSelection
ptr Ptr EventSelection -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

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

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

eventSelection_time :: AttrLabelProxy "time"
eventSelection_time = AttrLabelProxy

#endif


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

-- | Set the value of the “@requestor@” 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' #requestor
-- @
clearEventSelectionRequestor :: MonadIO m => EventSelection -> m ()
clearEventSelectionRequestor :: forall (m :: * -> *). MonadIO m => EventSelection -> m ()
clearEventSelectionRequestor EventSelection
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
$ EventSelection -> (Ptr EventSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSelection
s ((Ptr EventSelection -> IO ()) -> IO ())
-> (Ptr EventSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventSelection
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventSelection
ptr Ptr EventSelection -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (Ptr Window
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Window.Window)

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

eventSelection_requestor :: AttrLabelProxy "requestor"
eventSelection_requestor = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventSelection
type instance O.AttributeList EventSelection = EventSelectionAttributeList
type EventSelectionAttributeList = ('[ '("type", EventSelectionTypeFieldInfo), '("window", EventSelectionWindowFieldInfo), '("sendEvent", EventSelectionSendEventFieldInfo), '("selection", EventSelectionSelectionFieldInfo), '("target", EventSelectionTargetFieldInfo), '("property", EventSelectionPropertyFieldInfo), '("time", EventSelectionTimeFieldInfo), '("requestor", EventSelectionRequestorFieldInfo)] :: [(Symbol, DK.Type)])
#endif

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

instance (info ~ ResolveEventSelectionMethod t EventSelection, O.OverloadedMethod info EventSelection p) => OL.IsLabel t (EventSelection -> 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 ~ ResolveEventSelectionMethod t EventSelection, O.OverloadedMethod info EventSelection p, R.HasField t EventSelection p) => R.HasField t EventSelection p where
    getField = O.overloadedMethod @info

#endif

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

#endif