#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
       && !defined(__HADDOCK_VERSION__))
module GI.Gdk.Structs.EventKey
    (
    EventKey(..)                            ,
    newZeroEventKey                         ,
    noEventKey                              ,
 
#if ENABLE_OVERLOADING
    eventKey_group                          ,
#endif
    getEventKeyGroup                        ,
    setEventKeyGroup                        ,
#if ENABLE_OVERLOADING
    eventKey_hardwareKeycode                ,
#endif
    getEventKeyHardwareKeycode              ,
    setEventKeyHardwareKeycode              ,
#if ENABLE_OVERLOADING
    eventKey_isModifier                     ,
#endif
    getEventKeyIsModifier                   ,
    setEventKeyIsModifier                   ,
#if ENABLE_OVERLOADING
    eventKey_keyval                         ,
#endif
    getEventKeyKeyval                       ,
    setEventKeyKeyval                       ,
#if ENABLE_OVERLOADING
    eventKey_length                         ,
#endif
    getEventKeyLength                       ,
    setEventKeyLength                       ,
#if ENABLE_OVERLOADING
    eventKey_sendEvent                      ,
#endif
    getEventKeySendEvent                    ,
    setEventKeySendEvent                    ,
#if ENABLE_OVERLOADING
    eventKey_state                          ,
#endif
    getEventKeyState                        ,
    setEventKeyState                        ,
    clearEventKeyString                     ,
#if ENABLE_OVERLOADING
    eventKey_string                         ,
#endif
    getEventKeyString                       ,
    setEventKeyString                       ,
#if ENABLE_OVERLOADING
    eventKey_time                           ,
#endif
    getEventKeyTime                         ,
    setEventKeyTime                         ,
#if ENABLE_OVERLOADING
    eventKey_type                           ,
#endif
    getEventKeyType                         ,
    setEventKeyType                         ,
    clearEventKeyWindow                     ,
#if ENABLE_OVERLOADING
    eventKey_window                         ,
#endif
    getEventKeyWindow                       ,
    setEventKeyWindow                       ,
    ) 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
newtype EventKey = EventKey (ManagedPtr EventKey)
instance WrappedPtr EventKey where
    wrappedPtrCalloc = callocBytes 56
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 56 >=> wrapPtr EventKey)
    wrappedPtrFree = Just ptr_to_g_free
newZeroEventKey :: MonadIO m => m EventKey
newZeroEventKey = liftIO $ wrappedPtrCalloc >>= wrapPtr EventKey
instance tag ~ 'AttrSet => Constructible EventKey tag where
    new _ attrs = do
        o <- newZeroEventKey
        GI.Attributes.set o attrs
        return o
noEventKey :: Maybe EventKey
noEventKey = Nothing
getEventKeyType :: MonadIO m => EventKey -> m Gdk.Enums.EventType
getEventKeyType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CInt
    let val' = (toEnum . fromIntegral) val
    return val'
setEventKeyType :: MonadIO m => EventKey -> Gdk.Enums.EventType -> m ()
setEventKeyType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CInt)
#if ENABLE_OVERLOADING
data EventKeyTypeFieldInfo
instance AttrInfo EventKeyTypeFieldInfo where
    type AttrAllowedOps EventKeyTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeyTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrBaseTypeConstraint EventKeyTypeFieldInfo = (~) EventKey
    type AttrGetType EventKeyTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventKeyTypeFieldInfo = "type"
    type AttrOrigin EventKeyTypeFieldInfo = EventKey
    attrGet _ = getEventKeyType
    attrSet _ = setEventKeyType
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_type :: AttrLabelProxy "type"
eventKey_type = AttrLabelProxy
#endif
getEventKeyWindow :: MonadIO m => EventKey -> m (Maybe Gdk.Window.Window)
getEventKeyWindow 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
setEventKeyWindow :: MonadIO m => EventKey -> Ptr Gdk.Window.Window -> m ()
setEventKeyWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventKeyWindow :: MonadIO m => EventKey -> m ()
clearEventKeyWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
#if ENABLE_OVERLOADING
data EventKeyWindowFieldInfo
instance AttrInfo EventKeyWindowFieldInfo where
    type AttrAllowedOps EventKeyWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventKeyWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventKeyWindowFieldInfo = (~) EventKey
    type AttrGetType EventKeyWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventKeyWindowFieldInfo = "window"
    type AttrOrigin EventKeyWindowFieldInfo = EventKey
    attrGet _ = getEventKeyWindow
    attrSet _ = setEventKeyWindow
    attrConstruct = undefined
    attrClear _ = clearEventKeyWindow
eventKey_window :: AttrLabelProxy "window"
eventKey_window = AttrLabelProxy
#endif
getEventKeySendEvent :: MonadIO m => EventKey -> m Int8
getEventKeySendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int8
    return val
setEventKeySendEvent :: MonadIO m => EventKey -> Int8 -> m ()
setEventKeySendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int8)
#if ENABLE_OVERLOADING
data EventKeySendEventFieldInfo
instance AttrInfo EventKeySendEventFieldInfo where
    type AttrAllowedOps EventKeySendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeySendEventFieldInfo = (~) Int8
    type AttrBaseTypeConstraint EventKeySendEventFieldInfo = (~) EventKey
    type AttrGetType EventKeySendEventFieldInfo = Int8
    type AttrLabel EventKeySendEventFieldInfo = "send_event"
    type AttrOrigin EventKeySendEventFieldInfo = EventKey
    attrGet _ = getEventKeySendEvent
    attrSet _ = setEventKeySendEvent
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_sendEvent :: AttrLabelProxy "sendEvent"
eventKey_sendEvent = AttrLabelProxy
#endif
getEventKeyTime :: MonadIO m => EventKey -> m Word32
getEventKeyTime s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: IO Word32
    return val
setEventKeyTime :: MonadIO m => EventKey -> Word32 -> m ()
setEventKeyTime s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 20) (val :: Word32)
#if ENABLE_OVERLOADING
data EventKeyTimeFieldInfo
instance AttrInfo EventKeyTimeFieldInfo where
    type AttrAllowedOps EventKeyTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeyTimeFieldInfo = (~) Word32
    type AttrBaseTypeConstraint EventKeyTimeFieldInfo = (~) EventKey
    type AttrGetType EventKeyTimeFieldInfo = Word32
    type AttrLabel EventKeyTimeFieldInfo = "time"
    type AttrOrigin EventKeyTimeFieldInfo = EventKey
    attrGet _ = getEventKeyTime
    attrSet _ = setEventKeyTime
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_time :: AttrLabelProxy "time"
eventKey_time = AttrLabelProxy
#endif
getEventKeyState :: MonadIO m => EventKey -> m [Gdk.Flags.ModifierType]
getEventKeyState s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CUInt
    let val' = wordToGFlags val
    return val'
setEventKeyState :: MonadIO m => EventKey -> [Gdk.Flags.ModifierType] -> m ()
setEventKeyState s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = gflagsToWord val
    poke (ptr `plusPtr` 24) (val' :: CUInt)
#if ENABLE_OVERLOADING
data EventKeyStateFieldInfo
instance AttrInfo EventKeyStateFieldInfo where
    type AttrAllowedOps EventKeyStateFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeyStateFieldInfo = (~) [Gdk.Flags.ModifierType]
    type AttrBaseTypeConstraint EventKeyStateFieldInfo = (~) EventKey
    type AttrGetType EventKeyStateFieldInfo = [Gdk.Flags.ModifierType]
    type AttrLabel EventKeyStateFieldInfo = "state"
    type AttrOrigin EventKeyStateFieldInfo = EventKey
    attrGet _ = getEventKeyState
    attrSet _ = setEventKeyState
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_state :: AttrLabelProxy "state"
eventKey_state = AttrLabelProxy
#endif
getEventKeyKeyval :: MonadIO m => EventKey -> m Word32
getEventKeyKeyval s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 28) :: IO Word32
    return val
setEventKeyKeyval :: MonadIO m => EventKey -> Word32 -> m ()
setEventKeyKeyval s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 28) (val :: Word32)
#if ENABLE_OVERLOADING
data EventKeyKeyvalFieldInfo
instance AttrInfo EventKeyKeyvalFieldInfo where
    type AttrAllowedOps EventKeyKeyvalFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeyKeyvalFieldInfo = (~) Word32
    type AttrBaseTypeConstraint EventKeyKeyvalFieldInfo = (~) EventKey
    type AttrGetType EventKeyKeyvalFieldInfo = Word32
    type AttrLabel EventKeyKeyvalFieldInfo = "keyval"
    type AttrOrigin EventKeyKeyvalFieldInfo = EventKey
    attrGet _ = getEventKeyKeyval
    attrSet _ = setEventKeyKeyval
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_keyval :: AttrLabelProxy "keyval"
eventKey_keyval = AttrLabelProxy
#endif
getEventKeyLength :: MonadIO m => EventKey -> m Int32
getEventKeyLength s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO Int32
    return val
setEventKeyLength :: MonadIO m => EventKey -> Int32 -> m ()
setEventKeyLength s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Int32)
#if ENABLE_OVERLOADING
data EventKeyLengthFieldInfo
instance AttrInfo EventKeyLengthFieldInfo where
    type AttrAllowedOps EventKeyLengthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeyLengthFieldInfo = (~) Int32
    type AttrBaseTypeConstraint EventKeyLengthFieldInfo = (~) EventKey
    type AttrGetType EventKeyLengthFieldInfo = Int32
    type AttrLabel EventKeyLengthFieldInfo = "length"
    type AttrOrigin EventKeyLengthFieldInfo = EventKey
    attrGet _ = getEventKeyLength
    attrSet _ = setEventKeyLength
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_length :: AttrLabelProxy "length"
eventKey_length = AttrLabelProxy
#endif
getEventKeyString :: MonadIO m => EventKey -> m (Maybe T.Text)
getEventKeyString s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result
setEventKeyString :: MonadIO m => EventKey -> CString -> m ()
setEventKeyString s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (val :: CString)
clearEventKeyString :: MonadIO m => EventKey -> m ()
clearEventKeyString s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (FP.nullPtr :: CString)
#if ENABLE_OVERLOADING
data EventKeyStringFieldInfo
instance AttrInfo EventKeyStringFieldInfo where
    type AttrAllowedOps EventKeyStringFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventKeyStringFieldInfo = (~) CString
    type AttrBaseTypeConstraint EventKeyStringFieldInfo = (~) EventKey
    type AttrGetType EventKeyStringFieldInfo = Maybe T.Text
    type AttrLabel EventKeyStringFieldInfo = "string"
    type AttrOrigin EventKeyStringFieldInfo = EventKey
    attrGet _ = getEventKeyString
    attrSet _ = setEventKeyString
    attrConstruct = undefined
    attrClear _ = clearEventKeyString
eventKey_string :: AttrLabelProxy "string"
eventKey_string = AttrLabelProxy
#endif
getEventKeyHardwareKeycode :: MonadIO m => EventKey -> m Word16
getEventKeyHardwareKeycode s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO Word16
    return val
setEventKeyHardwareKeycode :: MonadIO m => EventKey -> Word16 -> m ()
setEventKeyHardwareKeycode s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (val :: Word16)
#if ENABLE_OVERLOADING
data EventKeyHardwareKeycodeFieldInfo
instance AttrInfo EventKeyHardwareKeycodeFieldInfo where
    type AttrAllowedOps EventKeyHardwareKeycodeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeyHardwareKeycodeFieldInfo = (~) Word16
    type AttrBaseTypeConstraint EventKeyHardwareKeycodeFieldInfo = (~) EventKey
    type AttrGetType EventKeyHardwareKeycodeFieldInfo = Word16
    type AttrLabel EventKeyHardwareKeycodeFieldInfo = "hardware_keycode"
    type AttrOrigin EventKeyHardwareKeycodeFieldInfo = EventKey
    attrGet _ = getEventKeyHardwareKeycode
    attrSet _ = setEventKeyHardwareKeycode
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_hardwareKeycode :: AttrLabelProxy "hardwareKeycode"
eventKey_hardwareKeycode = AttrLabelProxy
#endif
getEventKeyGroup :: MonadIO m => EventKey -> m Word8
getEventKeyGroup s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 50) :: IO Word8
    return val
setEventKeyGroup :: MonadIO m => EventKey -> Word8 -> m ()
setEventKeyGroup s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 50) (val :: Word8)
#if ENABLE_OVERLOADING
data EventKeyGroupFieldInfo
instance AttrInfo EventKeyGroupFieldInfo where
    type AttrAllowedOps EventKeyGroupFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeyGroupFieldInfo = (~) Word8
    type AttrBaseTypeConstraint EventKeyGroupFieldInfo = (~) EventKey
    type AttrGetType EventKeyGroupFieldInfo = Word8
    type AttrLabel EventKeyGroupFieldInfo = "group"
    type AttrOrigin EventKeyGroupFieldInfo = EventKey
    attrGet _ = getEventKeyGroup
    attrSet _ = setEventKeyGroup
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_group :: AttrLabelProxy "group"
eventKey_group = AttrLabelProxy
#endif
getEventKeyIsModifier :: MonadIO m => EventKey -> m Word32
getEventKeyIsModifier s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 52) :: IO Word32
    return val
setEventKeyIsModifier :: MonadIO m => EventKey -> Word32 -> m ()
setEventKeyIsModifier s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 52) (val :: Word32)
#if ENABLE_OVERLOADING
data EventKeyIsModifierFieldInfo
instance AttrInfo EventKeyIsModifierFieldInfo where
    type AttrAllowedOps EventKeyIsModifierFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventKeyIsModifierFieldInfo = (~) Word32
    type AttrBaseTypeConstraint EventKeyIsModifierFieldInfo = (~) EventKey
    type AttrGetType EventKeyIsModifierFieldInfo = Word32
    type AttrLabel EventKeyIsModifierFieldInfo = "is_modifier"
    type AttrOrigin EventKeyIsModifierFieldInfo = EventKey
    attrGet _ = getEventKeyIsModifier
    attrSet _ = setEventKeyIsModifier
    attrConstruct = undefined
    attrClear _ = undefined
eventKey_isModifier :: AttrLabelProxy "isModifier"
eventKey_isModifier = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList EventKey
type instance O.AttributeList EventKey = EventKeyAttributeList
type EventKeyAttributeList = ('[ '("type", EventKeyTypeFieldInfo), '("window", EventKeyWindowFieldInfo), '("sendEvent", EventKeySendEventFieldInfo), '("time", EventKeyTimeFieldInfo), '("state", EventKeyStateFieldInfo), '("keyval", EventKeyKeyvalFieldInfo), '("length", EventKeyLengthFieldInfo), '("string", EventKeyStringFieldInfo), '("hardwareKeycode", EventKeyHardwareKeycodeFieldInfo), '("group", EventKeyGroupFieldInfo), '("isModifier", EventKeyIsModifierFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveEventKeyMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventKeyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventKeyMethod t EventKey, O.MethodInfo info EventKey p) => OL.IsLabel t (EventKey -> 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