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

Generated when the pointer enters or leaves a window.
-}

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

module GI.Gdk.Structs.EventCrossing
    (

-- * Exported types
    EventCrossing(..)                       ,
    newZeroEventCrossing                    ,
    noEventCrossing                         ,


 -- * Properties
-- ** detail #attr:detail#
{- | the kind of crossing that happened ('GI.Gdk.Enums.NotifyTypeInferior',
 'GI.Gdk.Enums.NotifyTypeAncestor', 'GI.Gdk.Enums.NotifyTypeVirtual', 'GI.Gdk.Enums.NotifyTypeNonlinear' or
 'GI.Gdk.Enums.NotifyTypeNonlinearVirtual').
-}
#if ENABLE_OVERLOADING
    eventCrossing_detail                    ,
#endif
    getEventCrossingDetail                  ,
    setEventCrossingDetail                  ,


-- ** focus #attr:focus#
{- | 'True' if /@window@/ is the focus window or an inferior.
-}
#if ENABLE_OVERLOADING
    eventCrossing_focus                     ,
#endif
    getEventCrossingFocus                   ,
    setEventCrossingFocus                   ,


-- ** mode #attr:mode#
{- | the crossing mode ('GI.Gdk.Enums.CrossingModeNormal', 'GI.Gdk.Enums.CrossingModeGrab',
 'GI.Gdk.Enums.CrossingModeUngrab', 'GI.Gdk.Enums.CrossingModeGtkGrab', 'GI.Gdk.Enums.CrossingModeGtkUngrab' or
 'GI.Gdk.Enums.CrossingModeStateChanged').  'GI.Gdk.Enums.CrossingModeGtkGrab', 'GI.Gdk.Enums.CrossingModeGtkUngrab',
 and 'GI.Gdk.Enums.CrossingModeStateChanged' were added in 2.14 and are always synthesized,
 never native.
-}
#if ENABLE_OVERLOADING
    eventCrossing_mode                      ,
#endif
    getEventCrossingMode                    ,
    setEventCrossingMode                    ,


-- ** sendEvent #attr:sendEvent#
{- | 'True' if the event was sent explicitly.
-}
#if ENABLE_OVERLOADING
    eventCrossing_sendEvent                 ,
#endif
    getEventCrossingSendEvent               ,
    setEventCrossingSendEvent               ,


-- ** state #attr:state#
{- | a bit-mask representing the state of
  the modifier keys (e.g. Control, Shift and Alt) and the pointer
  buttons. See 'GI.Gdk.Flags.ModifierType'.
-}
#if ENABLE_OVERLOADING
    eventCrossing_state                     ,
#endif
    getEventCrossingState                   ,
    setEventCrossingState                   ,


-- ** subwindow #attr:subwindow#
{- | the window that was entered or left.
-}
    clearEventCrossingSubwindow             ,
#if ENABLE_OVERLOADING
    eventCrossing_subwindow                 ,
#endif
    getEventCrossingSubwindow               ,
    setEventCrossingSubwindow               ,


-- ** time #attr:time#
{- | the time of the event in milliseconds.
-}
#if ENABLE_OVERLOADING
    eventCrossing_time                      ,
#endif
    getEventCrossingTime                    ,
    setEventCrossingTime                    ,


-- ** type #attr:type#
{- | the type of the event ('GI.Gdk.Enums.EventTypeEnterNotify' or 'GI.Gdk.Enums.EventTypeLeaveNotify').
-}
#if ENABLE_OVERLOADING
    eventCrossing_type                      ,
#endif
    getEventCrossingType                    ,
    setEventCrossingType                    ,


-- ** window #attr:window#
{- | the window which received the event.
-}
    clearEventCrossingWindow                ,
#if ENABLE_OVERLOADING
    eventCrossing_window                    ,
#endif
    getEventCrossingWindow                  ,
    setEventCrossingWindow                  ,


-- ** x #attr:x#
{- | the x coordinate of the pointer relative to the window.
-}
#if ENABLE_OVERLOADING
    eventCrossing_x                         ,
#endif
    getEventCrossingX                       ,
    setEventCrossingX                       ,


-- ** xRoot #attr:xRoot#
{- | the x coordinate of the pointer relative to the root of the screen.
-}
#if ENABLE_OVERLOADING
    eventCrossing_xRoot                     ,
#endif
    getEventCrossingXRoot                   ,
    setEventCrossingXRoot                   ,


-- ** y #attr:y#
{- | the y coordinate of the pointer relative to the window.
-}
#if ENABLE_OVERLOADING
    eventCrossing_y                         ,
#endif
    getEventCrossingY                       ,
    setEventCrossingY                       ,


-- ** yRoot #attr:yRoot#
{- | the y coordinate of the pointer relative to the root of the screen.
-}
#if ENABLE_OVERLOADING
    eventCrossing_yRoot                     ,
#endif
    getEventCrossingYRoot                   ,
    setEventCrossingYRoot                   ,




    ) 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.GClosure as B.GClosure
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.GI.Base.Properties as B.Properties
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 qualified GHC.OverloadedLabels as OL

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

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `EventCrossing`.
noEventCrossing :: Maybe EventCrossing
noEventCrossing = 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' eventCrossing #type
@
-}
getEventCrossingType :: MonadIO m => EventCrossing -> m Gdk.Enums.EventType
getEventCrossingType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CInt
    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' eventCrossing [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingType :: MonadIO m => EventCrossing -> Gdk.Enums.EventType -> m ()
setEventCrossingType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CInt)

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

eventCrossing_type :: AttrLabelProxy "type"
eventCrossing_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' eventCrossing #window
@
-}
getEventCrossingWindow :: MonadIO m => EventCrossing -> m (Maybe Gdk.Window.Window)
getEventCrossingWindow 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' eventCrossing [ #window 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingWindow :: MonadIO m => EventCrossing -> Ptr Gdk.Window.Window -> m ()
setEventCrossingWindow 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
@
-}
clearEventCrossingWindow :: MonadIO m => EventCrossing -> m ()
clearEventCrossingWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)

#if ENABLE_OVERLOADING
data EventCrossingWindowFieldInfo
instance AttrInfo EventCrossingWindowFieldInfo where
    type AttrAllowedOps EventCrossingWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventCrossingWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventCrossingWindowFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventCrossingWindowFieldInfo = "window"
    type AttrOrigin EventCrossingWindowFieldInfo = EventCrossing
    attrGet _ = getEventCrossingWindow
    attrSet _ = setEventCrossingWindow
    attrConstruct = undefined
    attrClear _ = clearEventCrossingWindow

eventCrossing_window :: AttrLabelProxy "window"
eventCrossing_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' eventCrossing #sendEvent
@
-}
getEventCrossingSendEvent :: MonadIO m => EventCrossing -> m Int8
getEventCrossingSendEvent 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' eventCrossing [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingSendEvent :: MonadIO m => EventCrossing -> Int8 -> m ()
setEventCrossingSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int8)

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

eventCrossing_sendEvent :: AttrLabelProxy "sendEvent"
eventCrossing_sendEvent = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #subwindow
@
-}
getEventCrossingSubwindow :: MonadIO m => EventCrossing -> m (Maybe Gdk.Window.Window)
getEventCrossingSubwindow s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: 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 “@subwindow@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' eventCrossing [ #subwindow 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingSubwindow :: MonadIO m => EventCrossing -> Ptr Gdk.Window.Window -> m ()
setEventCrossingSubwindow s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Ptr Gdk.Window.Window)

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

#if ENABLE_OVERLOADING
data EventCrossingSubwindowFieldInfo
instance AttrInfo EventCrossingSubwindowFieldInfo where
    type AttrAllowedOps EventCrossingSubwindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventCrossingSubwindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventCrossingSubwindowFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingSubwindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventCrossingSubwindowFieldInfo = "subwindow"
    type AttrOrigin EventCrossingSubwindowFieldInfo = EventCrossing
    attrGet _ = getEventCrossingSubwindow
    attrSet _ = setEventCrossingSubwindow
    attrConstruct = undefined
    attrClear _ = clearEventCrossingSubwindow

eventCrossing_subwindow :: AttrLabelProxy "subwindow"
eventCrossing_subwindow = 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' eventCrossing #time
@
-}
getEventCrossingTime :: MonadIO m => EventCrossing -> m Word32
getEventCrossingTime s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO Word32
    return 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' eventCrossing [ #time 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingTime :: MonadIO m => EventCrossing -> Word32 -> m ()
setEventCrossingTime s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Word32)

#if ENABLE_OVERLOADING
data EventCrossingTimeFieldInfo
instance AttrInfo EventCrossingTimeFieldInfo where
    type AttrAllowedOps EventCrossingTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingTimeFieldInfo = (~) Word32
    type AttrBaseTypeConstraint EventCrossingTimeFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingTimeFieldInfo = Word32
    type AttrLabel EventCrossingTimeFieldInfo = "time"
    type AttrOrigin EventCrossingTimeFieldInfo = EventCrossing
    attrGet _ = getEventCrossingTime
    attrSet _ = setEventCrossingTime
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_time :: AttrLabelProxy "time"
eventCrossing_time = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #x
@
-}
getEventCrossingX :: MonadIO m => EventCrossing -> m Double
getEventCrossingX s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CDouble
    let val' = realToFrac val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventCrossing [ #x 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingX :: MonadIO m => EventCrossing -> Double -> m ()
setEventCrossingX s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 40) (val' :: CDouble)

#if ENABLE_OVERLOADING
data EventCrossingXFieldInfo
instance AttrInfo EventCrossingXFieldInfo where
    type AttrAllowedOps EventCrossingXFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingXFieldInfo = (~) Double
    type AttrBaseTypeConstraint EventCrossingXFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingXFieldInfo = Double
    type AttrLabel EventCrossingXFieldInfo = "x"
    type AttrOrigin EventCrossingXFieldInfo = EventCrossing
    attrGet _ = getEventCrossingX
    attrSet _ = setEventCrossingX
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_x :: AttrLabelProxy "x"
eventCrossing_x = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #y
@
-}
getEventCrossingY :: MonadIO m => EventCrossing -> m Double
getEventCrossingY s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO CDouble
    let val' = realToFrac val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventCrossing [ #y 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingY :: MonadIO m => EventCrossing -> Double -> m ()
setEventCrossingY s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 48) (val' :: CDouble)

#if ENABLE_OVERLOADING
data EventCrossingYFieldInfo
instance AttrInfo EventCrossingYFieldInfo where
    type AttrAllowedOps EventCrossingYFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingYFieldInfo = (~) Double
    type AttrBaseTypeConstraint EventCrossingYFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingYFieldInfo = Double
    type AttrLabel EventCrossingYFieldInfo = "y"
    type AttrOrigin EventCrossingYFieldInfo = EventCrossing
    attrGet _ = getEventCrossingY
    attrSet _ = setEventCrossingY
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_y :: AttrLabelProxy "y"
eventCrossing_y = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #xRoot
@
-}
getEventCrossingXRoot :: MonadIO m => EventCrossing -> m Double
getEventCrossingXRoot s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO CDouble
    let val' = realToFrac val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventCrossing [ #xRoot 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingXRoot :: MonadIO m => EventCrossing -> Double -> m ()
setEventCrossingXRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 56) (val' :: CDouble)

#if ENABLE_OVERLOADING
data EventCrossingXRootFieldInfo
instance AttrInfo EventCrossingXRootFieldInfo where
    type AttrAllowedOps EventCrossingXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingXRootFieldInfo = (~) Double
    type AttrBaseTypeConstraint EventCrossingXRootFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingXRootFieldInfo = Double
    type AttrLabel EventCrossingXRootFieldInfo = "x_root"
    type AttrOrigin EventCrossingXRootFieldInfo = EventCrossing
    attrGet _ = getEventCrossingXRoot
    attrSet _ = setEventCrossingXRoot
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_xRoot :: AttrLabelProxy "xRoot"
eventCrossing_xRoot = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #yRoot
@
-}
getEventCrossingYRoot :: MonadIO m => EventCrossing -> m Double
getEventCrossingYRoot s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO CDouble
    let val' = realToFrac val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventCrossing [ #yRoot 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingYRoot :: MonadIO m => EventCrossing -> Double -> m ()
setEventCrossingYRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 64) (val' :: CDouble)

#if ENABLE_OVERLOADING
data EventCrossingYRootFieldInfo
instance AttrInfo EventCrossingYRootFieldInfo where
    type AttrAllowedOps EventCrossingYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingYRootFieldInfo = (~) Double
    type AttrBaseTypeConstraint EventCrossingYRootFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingYRootFieldInfo = Double
    type AttrLabel EventCrossingYRootFieldInfo = "y_root"
    type AttrOrigin EventCrossingYRootFieldInfo = EventCrossing
    attrGet _ = getEventCrossingYRoot
    attrSet _ = setEventCrossingYRoot
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_yRoot :: AttrLabelProxy "yRoot"
eventCrossing_yRoot = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #mode
@
-}
getEventCrossingMode :: MonadIO m => EventCrossing -> m Gdk.Enums.CrossingMode
getEventCrossingMode s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 72) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventCrossing [ #mode 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingMode :: MonadIO m => EventCrossing -> Gdk.Enums.CrossingMode -> m ()
setEventCrossingMode s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 72) (val' :: CUInt)

#if ENABLE_OVERLOADING
data EventCrossingModeFieldInfo
instance AttrInfo EventCrossingModeFieldInfo where
    type AttrAllowedOps EventCrossingModeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingModeFieldInfo = (~) Gdk.Enums.CrossingMode
    type AttrBaseTypeConstraint EventCrossingModeFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingModeFieldInfo = Gdk.Enums.CrossingMode
    type AttrLabel EventCrossingModeFieldInfo = "mode"
    type AttrOrigin EventCrossingModeFieldInfo = EventCrossing
    attrGet _ = getEventCrossingMode
    attrSet _ = setEventCrossingMode
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_mode :: AttrLabelProxy "mode"
eventCrossing_mode = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #detail
@
-}
getEventCrossingDetail :: MonadIO m => EventCrossing -> m Gdk.Enums.NotifyType
getEventCrossingDetail s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 76) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventCrossing [ #detail 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingDetail :: MonadIO m => EventCrossing -> Gdk.Enums.NotifyType -> m ()
setEventCrossingDetail s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 76) (val' :: CUInt)

#if ENABLE_OVERLOADING
data EventCrossingDetailFieldInfo
instance AttrInfo EventCrossingDetailFieldInfo where
    type AttrAllowedOps EventCrossingDetailFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingDetailFieldInfo = (~) Gdk.Enums.NotifyType
    type AttrBaseTypeConstraint EventCrossingDetailFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingDetailFieldInfo = Gdk.Enums.NotifyType
    type AttrLabel EventCrossingDetailFieldInfo = "detail"
    type AttrOrigin EventCrossingDetailFieldInfo = EventCrossing
    attrGet _ = getEventCrossingDetail
    attrSet _ = setEventCrossingDetail
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_detail :: AttrLabelProxy "detail"
eventCrossing_detail = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #focus
@
-}
getEventCrossingFocus :: MonadIO m => EventCrossing -> m Bool
getEventCrossingFocus s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 80) :: IO CInt
    let val' = (/= 0) val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventCrossing [ #focus 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingFocus :: MonadIO m => EventCrossing -> Bool -> m ()
setEventCrossingFocus s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 80) (val' :: CInt)

#if ENABLE_OVERLOADING
data EventCrossingFocusFieldInfo
instance AttrInfo EventCrossingFocusFieldInfo where
    type AttrAllowedOps EventCrossingFocusFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingFocusFieldInfo = (~) Bool
    type AttrBaseTypeConstraint EventCrossingFocusFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingFocusFieldInfo = Bool
    type AttrLabel EventCrossingFocusFieldInfo = "focus"
    type AttrOrigin EventCrossingFocusFieldInfo = EventCrossing
    attrGet _ = getEventCrossingFocus
    attrSet _ = setEventCrossingFocus
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_focus :: AttrLabelProxy "focus"
eventCrossing_focus = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventCrossing #state
@
-}
getEventCrossingState :: MonadIO m => EventCrossing -> m [Gdk.Flags.ModifierType]
getEventCrossingState s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 84) :: IO CUInt
    let val' = wordToGFlags val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventCrossing [ #state 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventCrossingState :: MonadIO m => EventCrossing -> [Gdk.Flags.ModifierType] -> m ()
setEventCrossingState s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = gflagsToWord val
    poke (ptr `plusPtr` 84) (val' :: CUInt)

#if ENABLE_OVERLOADING
data EventCrossingStateFieldInfo
instance AttrInfo EventCrossingStateFieldInfo where
    type AttrAllowedOps EventCrossingStateFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventCrossingStateFieldInfo = (~) [Gdk.Flags.ModifierType]
    type AttrBaseTypeConstraint EventCrossingStateFieldInfo = (~) EventCrossing
    type AttrGetType EventCrossingStateFieldInfo = [Gdk.Flags.ModifierType]
    type AttrLabel EventCrossingStateFieldInfo = "state"
    type AttrOrigin EventCrossingStateFieldInfo = EventCrossing
    attrGet _ = getEventCrossingState
    attrSet _ = setEventCrossingState
    attrConstruct = undefined
    attrClear _ = undefined

eventCrossing_state :: AttrLabelProxy "state"
eventCrossing_state = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList EventCrossing
type instance O.AttributeList EventCrossing = EventCrossingAttributeList
type EventCrossingAttributeList = ('[ '("type", EventCrossingTypeFieldInfo), '("window", EventCrossingWindowFieldInfo), '("sendEvent", EventCrossingSendEventFieldInfo), '("subwindow", EventCrossingSubwindowFieldInfo), '("time", EventCrossingTimeFieldInfo), '("x", EventCrossingXFieldInfo), '("y", EventCrossingYFieldInfo), '("xRoot", EventCrossingXRootFieldInfo), '("yRoot", EventCrossingYRootFieldInfo), '("mode", EventCrossingModeFieldInfo), '("detail", EventCrossingDetailFieldInfo), '("focus", EventCrossingFocusFieldInfo), '("state", EventCrossingStateFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveEventCrossingMethod t EventCrossing, O.MethodInfo info EventCrossing p) => OL.IsLabel t (EventCrossing -> 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