{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Generated when the state of a toplevel window changes.

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

module GI.Gdk.Structs.EventWindowState
    ( 

-- * Exported types
    EventWindowState(..)                    ,
    newZeroEventWindowState                 ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveEventWindowStateMethod           ,
#endif



 -- * Properties


-- ** changedMask #attr:changedMask#
-- | mask specifying what flags have changed.

#if defined(ENABLE_OVERLOADING)
    eventWindowState_changedMask            ,
#endif
    getEventWindowStateChangedMask          ,
    setEventWindowStateChangedMask          ,


-- ** newWindowState #attr:newWindowState#
-- | the new window state, a combination of
--   t'GI.Gdk.Flags.WindowState' bits.

#if defined(ENABLE_OVERLOADING)
    eventWindowState_newWindowState         ,
#endif
    getEventWindowStateNewWindowState       ,
    setEventWindowStateNewWindowState       ,


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

#if defined(ENABLE_OVERLOADING)
    eventWindowState_sendEvent              ,
#endif
    getEventWindowStateSendEvent            ,
    setEventWindowStateSendEvent            ,


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

#if defined(ENABLE_OVERLOADING)
    eventWindowState_type                   ,
#endif
    getEventWindowStateType                 ,
    setEventWindowStateType                 ,


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

    clearEventWindowStateWindow             ,
#if defined(ENABLE_OVERLOADING)
    eventWindowState_window                 ,
#endif
    getEventWindowStateWindow               ,
    setEventWindowStateWindow               ,




    ) 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.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.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.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window

#endif

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

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

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


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

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

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

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

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

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

eventWindowState_sendEvent :: AttrLabelProxy "sendEvent"
eventWindowState_sendEvent = AttrLabelProxy

#endif


-- | Get the value of the “@changed_mask@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventWindowState #changedMask
-- @
getEventWindowStateChangedMask :: MonadIO m => EventWindowState -> m [Gdk.Flags.WindowState]
getEventWindowStateChangedMask :: forall (m :: * -> *).
MonadIO m =>
EventWindowState -> m [WindowState]
getEventWindowStateChangedMask EventWindowState
s = IO [WindowState] -> m [WindowState]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [WindowState] -> m [WindowState])
-> IO [WindowState] -> m [WindowState]
forall a b. (a -> b) -> a -> b
$ EventWindowState
-> (Ptr EventWindowState -> IO [WindowState]) -> IO [WindowState]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventWindowState
s ((Ptr EventWindowState -> IO [WindowState]) -> IO [WindowState])
-> (Ptr EventWindowState -> IO [WindowState]) -> IO [WindowState]
forall a b. (a -> b) -> a -> b
$ \Ptr EventWindowState
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventWindowState
ptr Ptr EventWindowState -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO CUInt
    let val' :: [WindowState]
val' = CUInt -> [WindowState]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
    [WindowState] -> IO [WindowState]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [WindowState]
val'

-- | Set the value of the “@changed_mask@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventWindowState [ #changedMask 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventWindowStateChangedMask :: MonadIO m => EventWindowState -> [Gdk.Flags.WindowState] -> m ()
setEventWindowStateChangedMask :: forall (m :: * -> *).
MonadIO m =>
EventWindowState -> [WindowState] -> m ()
setEventWindowStateChangedMask EventWindowState
s [WindowState]
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
$ EventWindowState -> (Ptr EventWindowState -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventWindowState
s ((Ptr EventWindowState -> IO ()) -> IO ())
-> (Ptr EventWindowState -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventWindowState
ptr -> do
    let val' :: CUInt
val' = [WindowState] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [WindowState]
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventWindowState
ptr Ptr EventWindowState -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (CUInt
val' :: CUInt)

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

eventWindowState_changedMask :: AttrLabelProxy "changedMask"
eventWindowState_changedMask = AttrLabelProxy

#endif


-- | Get the value of the “@new_window_state@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventWindowState #newWindowState
-- @
getEventWindowStateNewWindowState :: MonadIO m => EventWindowState -> m [Gdk.Flags.WindowState]
getEventWindowStateNewWindowState :: forall (m :: * -> *).
MonadIO m =>
EventWindowState -> m [WindowState]
getEventWindowStateNewWindowState EventWindowState
s = IO [WindowState] -> m [WindowState]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [WindowState] -> m [WindowState])
-> IO [WindowState] -> m [WindowState]
forall a b. (a -> b) -> a -> b
$ EventWindowState
-> (Ptr EventWindowState -> IO [WindowState]) -> IO [WindowState]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventWindowState
s ((Ptr EventWindowState -> IO [WindowState]) -> IO [WindowState])
-> (Ptr EventWindowState -> IO [WindowState]) -> IO [WindowState]
forall a b. (a -> b) -> a -> b
$ \Ptr EventWindowState
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventWindowState
ptr Ptr EventWindowState -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO CUInt
    let val' :: [WindowState]
val' = CUInt -> [WindowState]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
    [WindowState] -> IO [WindowState]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [WindowState]
val'

-- | Set the value of the “@new_window_state@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventWindowState [ #newWindowState 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventWindowStateNewWindowState :: MonadIO m => EventWindowState -> [Gdk.Flags.WindowState] -> m ()
setEventWindowStateNewWindowState :: forall (m :: * -> *).
MonadIO m =>
EventWindowState -> [WindowState] -> m ()
setEventWindowStateNewWindowState EventWindowState
s [WindowState]
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
$ EventWindowState -> (Ptr EventWindowState -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventWindowState
s ((Ptr EventWindowState -> IO ()) -> IO ())
-> (Ptr EventWindowState -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventWindowState
ptr -> do
    let val' :: CUInt
val' = [WindowState] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [WindowState]
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventWindowState
ptr Ptr EventWindowState -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CUInt
val' :: CUInt)

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

eventWindowState_newWindowState :: AttrLabelProxy "newWindowState"
eventWindowState_newWindowState = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventWindowState
type instance O.AttributeList EventWindowState = EventWindowStateAttributeList
type EventWindowStateAttributeList = ('[ '("type", EventWindowStateTypeFieldInfo), '("window", EventWindowStateWindowFieldInfo), '("sendEvent", EventWindowStateSendEventFieldInfo), '("changedMask", EventWindowStateChangedMaskFieldInfo), '("newWindowState", EventWindowStateNewWindowStateFieldInfo)] :: [(Symbol, DK.Type)])
#endif

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

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

#endif

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

#endif