{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

Generated when a pointer or keyboard grab is broken. On X11, this happens
when the grab window becomes unviewable (i.e. it or one of its ancestors
is unmapped), or if the same application grabs the pointer or keyboard
again. Note that implicit grabs (which are initiated by button presses)
can also cause 'GI.Gdk.Structs.EventGrabBroken.EventGrabBroken' events.

/Since: 2.8/
-}

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

module GI.Gdk.Structs.EventGrabBroken
    (

-- * Exported types
    EventGrabBroken(..)                     ,
    newZeroEventGrabBroken                  ,
    noEventGrabBroken                       ,


 -- * Properties
-- ** grabWindow #attr:grabWindow#
{- | If this event is caused by another grab in the same
  application, /@grabWindow@/ contains the new grab window. Otherwise
  /@grabWindow@/ is 'Nothing'.
-}
    clearEventGrabBrokenGrabWindow          ,
#if ENABLE_OVERLOADING
    eventGrabBroken_grabWindow              ,
#endif
    getEventGrabBrokenGrabWindow            ,
    setEventGrabBrokenGrabWindow            ,


-- ** implicit #attr:implicit#
{- | 'True' if the broken grab was implicit
-}
#if ENABLE_OVERLOADING
    eventGrabBroken_implicit                ,
#endif
    getEventGrabBrokenImplicit              ,
    setEventGrabBrokenImplicit              ,


-- ** keyboard #attr:keyboard#
{- | 'True' if a keyboard grab was broken, 'False' if a pointer
  grab was broken
-}
#if ENABLE_OVERLOADING
    eventGrabBroken_keyboard                ,
#endif
    getEventGrabBrokenKeyboard              ,
    setEventGrabBrokenKeyboard              ,


-- ** sendEvent #attr:sendEvent#
{- | 'True' if the event was sent explicitly.
-}
#if ENABLE_OVERLOADING
    eventGrabBroken_sendEvent               ,
#endif
    getEventGrabBrokenSendEvent             ,
    setEventGrabBrokenSendEvent             ,


-- ** type #attr:type#
{- | the type of the event ('GI.Gdk.Enums.EventTypeGrabBroken')
-}
#if ENABLE_OVERLOADING
    eventGrabBroken_type                    ,
#endif
    getEventGrabBrokenType                  ,
    setEventGrabBrokenType                  ,


-- ** window #attr:window#
{- | the window which received the event, i.e. the window
  that previously owned the grab
-}
    clearEventGrabBrokenWindow              ,
#if ENABLE_OVERLOADING
    eventGrabBroken_window                  ,
#endif
    getEventGrabBrokenWindow                ,
    setEventGrabBrokenWindow                ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP

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

-- | Memory-managed wrapper type.
newtype EventGrabBroken = EventGrabBroken (ManagedPtr EventGrabBroken)
instance WrappedPtr EventGrabBroken where
    wrappedPtrCalloc = callocBytes 40
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 40 >=> wrapPtr EventGrabBroken)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `EventGrabBroken` struct initialized to zero.
newZeroEventGrabBroken :: MonadIO m => m EventGrabBroken
newZeroEventGrabBroken = liftIO $ wrappedPtrCalloc >>= wrapPtr EventGrabBroken

instance tag ~ 'AttrSet => Constructible EventGrabBroken tag where
    new _ attrs = do
        o <- newZeroEventGrabBroken
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `EventGrabBroken`.
noEventGrabBroken :: Maybe EventGrabBroken
noEventGrabBroken = Nothing

{- |
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' eventGrabBroken #type
@
-}
getEventGrabBrokenType :: MonadIO m => EventGrabBroken -> m Gdk.Enums.EventType
getEventGrabBrokenType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return 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' eventGrabBroken [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventGrabBrokenType :: MonadIO m => EventGrabBroken -> Gdk.Enums.EventType -> m ()
setEventGrabBrokenType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

#if ENABLE_OVERLOADING
data EventGrabBrokenTypeFieldInfo
instance AttrInfo EventGrabBrokenTypeFieldInfo where
    type AttrAllowedOps EventGrabBrokenTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventGrabBrokenTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrBaseTypeConstraint EventGrabBrokenTypeFieldInfo = (~) EventGrabBroken
    type AttrGetType EventGrabBrokenTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventGrabBrokenTypeFieldInfo = "type"
    type AttrOrigin EventGrabBrokenTypeFieldInfo = EventGrabBroken
    attrGet _ = getEventGrabBrokenType
    attrSet _ = setEventGrabBrokenType
    attrConstruct = undefined
    attrClear _ = undefined

eventGrabBroken_type :: AttrLabelProxy "type"
eventGrabBroken_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' eventGrabBroken #window
@
-}
getEventGrabBrokenWindow :: MonadIO m => EventGrabBroken -> m (Maybe Gdk.Window.Window)
getEventGrabBrokenWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr Gdk.Window.Window)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject Gdk.Window.Window) val'
        return val''
    return 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' eventGrabBroken [ #window 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventGrabBrokenWindow :: MonadIO m => EventGrabBroken -> Ptr Gdk.Window.Window -> m ()
setEventGrabBrokenWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (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
@
-}
clearEventGrabBrokenWindow :: MonadIO m => EventGrabBroken -> m ()
clearEventGrabBrokenWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)

#if ENABLE_OVERLOADING
data EventGrabBrokenWindowFieldInfo
instance AttrInfo EventGrabBrokenWindowFieldInfo where
    type AttrAllowedOps EventGrabBrokenWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventGrabBrokenWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventGrabBrokenWindowFieldInfo = (~) EventGrabBroken
    type AttrGetType EventGrabBrokenWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventGrabBrokenWindowFieldInfo = "window"
    type AttrOrigin EventGrabBrokenWindowFieldInfo = EventGrabBroken
    attrGet _ = getEventGrabBrokenWindow
    attrSet _ = setEventGrabBrokenWindow
    attrConstruct = undefined
    attrClear _ = clearEventGrabBrokenWindow

eventGrabBroken_window :: AttrLabelProxy "window"
eventGrabBroken_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' eventGrabBroken #sendEvent
@
-}
getEventGrabBrokenSendEvent :: MonadIO m => EventGrabBroken -> m Int8
getEventGrabBrokenSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int8
    return 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' eventGrabBroken [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventGrabBrokenSendEvent :: MonadIO m => EventGrabBroken -> Int8 -> m ()
setEventGrabBrokenSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int8)

#if ENABLE_OVERLOADING
data EventGrabBrokenSendEventFieldInfo
instance AttrInfo EventGrabBrokenSendEventFieldInfo where
    type AttrAllowedOps EventGrabBrokenSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventGrabBrokenSendEventFieldInfo = (~) Int8
    type AttrBaseTypeConstraint EventGrabBrokenSendEventFieldInfo = (~) EventGrabBroken
    type AttrGetType EventGrabBrokenSendEventFieldInfo = Int8
    type AttrLabel EventGrabBrokenSendEventFieldInfo = "send_event"
    type AttrOrigin EventGrabBrokenSendEventFieldInfo = EventGrabBroken
    attrGet _ = getEventGrabBrokenSendEvent
    attrSet _ = setEventGrabBrokenSendEvent
    attrConstruct = undefined
    attrClear _ = undefined

eventGrabBroken_sendEvent :: AttrLabelProxy "sendEvent"
eventGrabBroken_sendEvent = AttrLabelProxy

#endif


{- |
Get the value of the “@keyboard@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' eventGrabBroken #keyboard
@
-}
getEventGrabBrokenKeyboard :: MonadIO m => EventGrabBroken -> m Bool
getEventGrabBrokenKeyboard s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: IO CInt
    let val' = (/= 0) val
    return val'

{- |
Set the value of the “@keyboard@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' eventGrabBroken [ #keyboard 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventGrabBrokenKeyboard :: MonadIO m => EventGrabBroken -> Bool -> m ()
setEventGrabBrokenKeyboard s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 20) (val' :: CInt)

#if ENABLE_OVERLOADING
data EventGrabBrokenKeyboardFieldInfo
instance AttrInfo EventGrabBrokenKeyboardFieldInfo where
    type AttrAllowedOps EventGrabBrokenKeyboardFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventGrabBrokenKeyboardFieldInfo = (~) Bool
    type AttrBaseTypeConstraint EventGrabBrokenKeyboardFieldInfo = (~) EventGrabBroken
    type AttrGetType EventGrabBrokenKeyboardFieldInfo = Bool
    type AttrLabel EventGrabBrokenKeyboardFieldInfo = "keyboard"
    type AttrOrigin EventGrabBrokenKeyboardFieldInfo = EventGrabBroken
    attrGet _ = getEventGrabBrokenKeyboard
    attrSet _ = setEventGrabBrokenKeyboard
    attrConstruct = undefined
    attrClear _ = undefined

eventGrabBroken_keyboard :: AttrLabelProxy "keyboard"
eventGrabBroken_keyboard = AttrLabelProxy

#endif


{- |
Get the value of the “@implicit@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' eventGrabBroken #implicit
@
-}
getEventGrabBrokenImplicit :: MonadIO m => EventGrabBroken -> m Bool
getEventGrabBrokenImplicit s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CInt
    let val' = (/= 0) val
    return val'

{- |
Set the value of the “@implicit@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' eventGrabBroken [ #implicit 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventGrabBrokenImplicit :: MonadIO m => EventGrabBroken -> Bool -> m ()
setEventGrabBrokenImplicit s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 24) (val' :: CInt)

#if ENABLE_OVERLOADING
data EventGrabBrokenImplicitFieldInfo
instance AttrInfo EventGrabBrokenImplicitFieldInfo where
    type AttrAllowedOps EventGrabBrokenImplicitFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventGrabBrokenImplicitFieldInfo = (~) Bool
    type AttrBaseTypeConstraint EventGrabBrokenImplicitFieldInfo = (~) EventGrabBroken
    type AttrGetType EventGrabBrokenImplicitFieldInfo = Bool
    type AttrLabel EventGrabBrokenImplicitFieldInfo = "implicit"
    type AttrOrigin EventGrabBrokenImplicitFieldInfo = EventGrabBroken
    attrGet _ = getEventGrabBrokenImplicit
    attrSet _ = setEventGrabBrokenImplicit
    attrConstruct = undefined
    attrClear _ = undefined

eventGrabBroken_implicit :: AttrLabelProxy "implicit"
eventGrabBroken_implicit = AttrLabelProxy

#endif


{- |
Get the value of the “@grab_window@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' eventGrabBroken #grabWindow
@
-}
getEventGrabBrokenGrabWindow :: MonadIO m => EventGrabBroken -> m (Maybe Gdk.Window.Window)
getEventGrabBrokenGrabWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO (Ptr Gdk.Window.Window)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject Gdk.Window.Window) val'
        return val''
    return result

{- |
Set the value of the “@grab_window@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' eventGrabBroken [ #grabWindow 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventGrabBrokenGrabWindow :: MonadIO m => EventGrabBroken -> Ptr Gdk.Window.Window -> m ()
setEventGrabBrokenGrabWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Ptr Gdk.Window.Window)

{- |
Set the value of the “@grab_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' #grabWindow
@
-}
clearEventGrabBrokenGrabWindow :: MonadIO m => EventGrabBroken -> m ()
clearEventGrabBrokenGrabWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (FP.nullPtr :: Ptr Gdk.Window.Window)

#if ENABLE_OVERLOADING
data EventGrabBrokenGrabWindowFieldInfo
instance AttrInfo EventGrabBrokenGrabWindowFieldInfo where
    type AttrAllowedOps EventGrabBrokenGrabWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventGrabBrokenGrabWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventGrabBrokenGrabWindowFieldInfo = (~) EventGrabBroken
    type AttrGetType EventGrabBrokenGrabWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventGrabBrokenGrabWindowFieldInfo = "grab_window"
    type AttrOrigin EventGrabBrokenGrabWindowFieldInfo = EventGrabBroken
    attrGet _ = getEventGrabBrokenGrabWindow
    attrSet _ = setEventGrabBrokenGrabWindow
    attrConstruct = undefined
    attrClear _ = clearEventGrabBrokenGrabWindow

eventGrabBroken_grabWindow :: AttrLabelProxy "grabWindow"
eventGrabBroken_grabWindow = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList EventGrabBroken
type instance O.AttributeList EventGrabBroken = EventGrabBrokenAttributeList
type EventGrabBrokenAttributeList = ('[ '("type", EventGrabBrokenTypeFieldInfo), '("window", EventGrabBrokenWindowFieldInfo), '("sendEvent", EventGrabBrokenSendEventFieldInfo), '("keyboard", EventGrabBrokenKeyboardFieldInfo), '("implicit", EventGrabBrokenImplicitFieldInfo), '("grabWindow", EventGrabBrokenGrabWindowFieldInfo)] :: [(Symbol, *)])
#endif

#if ENABLE_OVERLOADING
type family ResolveEventGrabBrokenMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventGrabBrokenMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveEventGrabBrokenMethod t EventGrabBroken, O.MethodInfo info EventGrabBroken p) => O.IsLabelProxy t (EventGrabBroken -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveEventGrabBrokenMethod t EventGrabBroken, O.MethodInfo info EventGrabBroken p) => O.IsLabel t (EventGrabBroken -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif

#endif