{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Describes a key press or key release event.

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

module GI.Gdk.Structs.EventKey
    ( 

-- * Exported types
    EventKey(..)                            ,
    newZeroEventKey                         ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveEventKeyMethod                   ,
#endif



 -- * Properties


-- ** group #attr:group#
-- | the keyboard group.

#if defined(ENABLE_OVERLOADING)
    eventKey_group                          ,
#endif
    getEventKeyGroup                        ,
    setEventKeyGroup                        ,


-- ** hardwareKeycode #attr:hardwareKeycode#
-- | the raw code of the key that was pressed or released.

#if defined(ENABLE_OVERLOADING)
    eventKey_hardwareKeycode                ,
#endif
    getEventKeyHardwareKeycode              ,
    setEventKeyHardwareKeycode              ,


-- ** isModifier #attr:isModifier#
-- | a flag that indicates if /@hardwareKeycode@/ is mapped to a
--   modifier. Since 2.10

#if defined(ENABLE_OVERLOADING)
    eventKey_isModifier                     ,
#endif
    getEventKeyIsModifier                   ,
    setEventKeyIsModifier                   ,


-- ** keyval #attr:keyval#
-- | the key that was pressed or released. See the
--   @gdk\/gdkkeysyms.h@ header file for a
--   complete list of GDK key codes.

#if defined(ENABLE_OVERLOADING)
    eventKey_keyval                         ,
#endif
    getEventKeyKeyval                       ,
    setEventKeyKeyval                       ,


-- ** length #attr:length#
-- | the length of /@string@/.

#if defined(ENABLE_OVERLOADING)
    eventKey_length                         ,
#endif
    getEventKeyLength                       ,
    setEventKeyLength                       ,


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

#if defined(ENABLE_OVERLOADING)
    eventKey_sendEvent                      ,
#endif
    getEventKeySendEvent                    ,
    setEventKeySendEvent                    ,


-- ** state #attr:state#
-- | a bit-mask representing the state of
--   the modifier keys (e.g. Control, Shift and Alt) and the pointer
--   buttons. See t'GI.Gdk.Flags.ModifierType'.

#if defined(ENABLE_OVERLOADING)
    eventKey_state                          ,
#endif
    getEventKeyState                        ,
    setEventKeyState                        ,


-- ** string #attr:string#
-- | a string containing an approximation of the text that
--   would result from this keypress. The only correct way to handle text
--   input of text is using input methods (see @/GtkIMContext/@), so this
--   field is deprecated and should never be used.
--   ('GI.Gdk.Functions.unicodeToKeyval' provides a non-deprecated way of getting
--   an approximate translation for a key.) The string is encoded in the
--   encoding of the current locale (Note: this for backwards compatibility:
--   strings in GTK+ and GDK are typically in UTF-8.) and NUL-terminated.
--   In some cases, the translation of the key code will be a single
--   NUL byte, in which case looking at /@length@/ is necessary to distinguish
--   it from the an empty translation.

    clearEventKeyString                     ,
#if defined(ENABLE_OVERLOADING)
    eventKey_string                         ,
#endif
    getEventKeyString                       ,
    setEventKeyString                       ,


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

#if defined(ENABLE_OVERLOADING)
    eventKey_time                           ,
#endif
    getEventKeyTime                         ,
    setEventKeyTime                         ,


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

#if defined(ENABLE_OVERLOADING)
    eventKey_type                           ,
#endif
    getEventKeyType                         ,
    setEventKeyType                         ,


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

    clearEventKeyWindow                     ,
#if defined(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.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.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.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 {-# 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 EventKey = EventKey (SP.ManagedPtr EventKey)
    deriving (EventKey -> EventKey -> Bool
(EventKey -> EventKey -> Bool)
-> (EventKey -> EventKey -> Bool) -> Eq EventKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventKey -> EventKey -> Bool
$c/= :: EventKey -> EventKey -> Bool
== :: EventKey -> EventKey -> Bool
$c== :: EventKey -> EventKey -> Bool
Eq)

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

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


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

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

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

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

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

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

eventKey_sendEvent :: AttrLabelProxy "sendEvent"
eventKey_sendEvent = 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' eventKey #time
-- @
getEventKeyTime :: MonadIO m => EventKey -> m Word32
getEventKeyTime :: forall (m :: * -> *). MonadIO m => EventKey -> m Word32
getEventKeyTime EventKey
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO Word32) -> IO Word32)
-> (Ptr EventKey -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

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

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

eventKey_time :: AttrLabelProxy "time"
eventKey_time = 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' eventKey #state
-- @
getEventKeyState :: MonadIO m => EventKey -> m [Gdk.Flags.ModifierType]
getEventKeyState :: forall (m :: * -> *). MonadIO m => EventKey -> m [ModifierType]
getEventKeyState EventKey
s = IO [ModifierType] -> m [ModifierType]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ModifierType] -> m [ModifierType])
-> IO [ModifierType] -> m [ModifierType]
forall a b. (a -> b) -> a -> b
$ EventKey
-> (Ptr EventKey -> IO [ModifierType]) -> IO [ModifierType]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO [ModifierType]) -> IO [ModifierType])
-> (Ptr EventKey -> IO [ModifierType]) -> IO [ModifierType]
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO CUInt
    let val' :: [ModifierType]
val' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
    [ModifierType] -> IO [ModifierType]
forall (m :: * -> *) a. Monad m => a -> m a
return [ModifierType]
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' eventKey [ #state 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventKeyState :: MonadIO m => EventKey -> [Gdk.Flags.ModifierType] -> m ()
setEventKeyState :: forall (m :: * -> *).
MonadIO m =>
EventKey -> [ModifierType] -> m ()
setEventKeyState EventKey
s [ModifierType]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO ()) -> IO ())
-> (Ptr EventKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    let val' :: CUInt
val' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CUInt
val' :: CUInt)

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

eventKey_state :: AttrLabelProxy "state"
eventKey_state = AttrLabelProxy

#endif


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

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

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

eventKey_keyval :: AttrLabelProxy "keyval"
eventKey_keyval = AttrLabelProxy

#endif


-- | Get the value of the “@length@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventKey #length
-- @
getEventKeyLength :: MonadIO m => EventKey -> m Int32
getEventKeyLength :: forall (m :: * -> *). MonadIO m => EventKey -> m Int32
getEventKeyLength EventKey
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO Int32) -> IO Int32)
-> (Ptr EventKey -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@length@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventKey [ #length 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventKeyLength :: MonadIO m => EventKey -> Int32 -> m ()
setEventKeyLength :: forall (m :: * -> *). MonadIO m => EventKey -> Int32 -> m ()
setEventKeyLength EventKey
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO ()) -> IO ())
-> (Ptr EventKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Int32
val :: Int32)

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

eventKey_length :: AttrLabelProxy "length"
eventKey_length = AttrLabelProxy

#endif


-- | Get the value of the “@string@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventKey #string
-- @
getEventKeyString :: MonadIO m => EventKey -> m (Maybe T.Text)
getEventKeyString :: forall (m :: * -> *). MonadIO m => EventKey -> m (Maybe Text)
getEventKeyString EventKey
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr EventKey -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@string@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventKey [ #string 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventKeyString :: MonadIO m => EventKey -> CString -> m ()
setEventKeyString :: forall (m :: * -> *). MonadIO m => EventKey -> CString -> m ()
setEventKeyString EventKey
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO ()) -> IO ())
-> (Ptr EventKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (CString
val :: CString)

-- | Set the value of the “@string@” 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' #string
-- @
clearEventKeyString :: MonadIO m => EventKey -> m ()
clearEventKeyString :: forall (m :: * -> *). MonadIO m => EventKey -> m ()
clearEventKeyString EventKey
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO ()) -> IO ())
-> (Ptr EventKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data EventKeyStringFieldInfo
instance AttrInfo EventKeyStringFieldInfo where
    type AttrBaseTypeConstraint EventKeyStringFieldInfo = (~) EventKey
    type AttrAllowedOps EventKeyStringFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventKeyStringFieldInfo = (~) CString
    type AttrTransferTypeConstraint EventKeyStringFieldInfo = (~)CString
    type AttrTransferType EventKeyStringFieldInfo = CString
    type AttrGetType EventKeyStringFieldInfo = Maybe T.Text
    type AttrLabel EventKeyStringFieldInfo = "string"
    type AttrOrigin EventKeyStringFieldInfo = EventKey
    attrGet = getEventKeyString
    attrSet = setEventKeyString
    attrConstruct = undefined
    attrClear = clearEventKeyString
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventKey.string"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventKey.html#g:attr:string"
        })

eventKey_string :: AttrLabelProxy "string"
eventKey_string = AttrLabelProxy

#endif


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

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

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

eventKey_hardwareKeycode :: AttrLabelProxy "hardwareKeycode"
eventKey_hardwareKeycode = AttrLabelProxy

#endif


-- | Get the value of the “@group@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventKey #group
-- @
getEventKeyGroup :: MonadIO m => EventKey -> m Word8
getEventKeyGroup :: forall (m :: * -> *). MonadIO m => EventKey -> m Word8
getEventKeyGroup EventKey
s = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO Word8) -> IO Word8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO Word8) -> IO Word8)
-> (Ptr EventKey -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    Word8
val <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
50) :: IO Word8
    Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
val

-- | Set the value of the “@group@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventKey [ #group 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventKeyGroup :: MonadIO m => EventKey -> Word8 -> m ()
setEventKeyGroup :: forall (m :: * -> *). MonadIO m => EventKey -> Word8 -> m ()
setEventKeyGroup EventKey
s Word8
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventKey -> (Ptr EventKey -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventKey
s ((Ptr EventKey -> IO ()) -> IO ())
-> (Ptr EventKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventKey
ptr -> do
    Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventKey
ptr Ptr EventKey -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
50) (Word8
val :: Word8)

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

eventKey_group :: AttrLabelProxy "group"
eventKey_group = AttrLabelProxy

#endif


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

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

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

eventKey_isModifier :: AttrLabelProxy "isModifier"
eventKey_isModifier = AttrLabelProxy

#endif



#if defined(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 defined(ENABLE_OVERLOADING)
type family ResolveEventKeyMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventKeyMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif