{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Describes a property change on a window.

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

module GI.Gdk.Structs.EventProperty
    ( 

-- * Exported types
    EventProperty(..)                       ,
    newZeroEventProperty                    ,
    noEventProperty                         ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveEventPropertyMethod              ,
#endif




 -- * Properties
-- ** atom #attr:atom#
-- | the property that was changed.

#if defined(ENABLE_OVERLOADING)
    eventProperty_atom                      ,
#endif
    getEventPropertyAtom                    ,


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

#if defined(ENABLE_OVERLOADING)
    eventProperty_sendEvent                 ,
#endif
    getEventPropertySendEvent               ,
    setEventPropertySendEvent               ,


-- ** state #attr:state#
-- | whether the property was changed
--   ('GI.Gdk.Enums.PropertyStateNewValue') or deleted ('GI.Gdk.Enums.PropertyStateDelete').

#if defined(ENABLE_OVERLOADING)
    eventProperty_state                     ,
#endif
    getEventPropertyState                   ,
    setEventPropertyState                   ,


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

#if defined(ENABLE_OVERLOADING)
    eventProperty_time                      ,
#endif
    getEventPropertyTime                    ,
    setEventPropertyTime                    ,


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

#if defined(ENABLE_OVERLOADING)
    eventProperty_type                      ,
#endif
    getEventPropertyType                    ,
    setEventPropertyType                    ,


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

    clearEventPropertyWindow                ,
#if defined(ENABLE_OVERLOADING)
    eventProperty_window                    ,
#endif
    getEventPropertyWindow                  ,
    setEventPropertyWindow                  ,




    ) 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.GI.Base.Signals as B.Signals
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.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom

-- | Memory-managed wrapper type.
newtype EventProperty = EventProperty (ManagedPtr EventProperty)
    deriving (EventProperty -> EventProperty -> Bool
(EventProperty -> EventProperty -> Bool)
-> (EventProperty -> EventProperty -> Bool) -> Eq EventProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventProperty -> EventProperty -> Bool
$c/= :: EventProperty -> EventProperty -> Bool
== :: EventProperty -> EventProperty -> Bool
$c== :: EventProperty -> EventProperty -> Bool
Eq)
instance WrappedPtr EventProperty where
    wrappedPtrCalloc :: IO (Ptr EventProperty)
wrappedPtrCalloc = Int -> IO (Ptr EventProperty)
forall a. Int -> IO (Ptr a)
callocBytes 40
    wrappedPtrCopy :: EventProperty -> IO EventProperty
wrappedPtrCopy = \p :: EventProperty
p -> EventProperty
-> (Ptr EventProperty -> IO EventProperty) -> IO EventProperty
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
p (Int -> Ptr EventProperty -> IO (Ptr EventProperty)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 40 (Ptr EventProperty -> IO (Ptr EventProperty))
-> (Ptr EventProperty -> IO EventProperty)
-> Ptr EventProperty
-> IO EventProperty
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventProperty -> EventProperty)
-> Ptr EventProperty -> IO EventProperty
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventProperty -> EventProperty
EventProperty)
    wrappedPtrFree :: Maybe (GDestroyNotify EventProperty)
wrappedPtrFree = GDestroyNotify EventProperty
-> Maybe (GDestroyNotify EventProperty)
forall a. a -> Maybe a
Just GDestroyNotify EventProperty
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `EventProperty` struct initialized to zero.
newZeroEventProperty :: MonadIO m => m EventProperty
newZeroEventProperty :: m EventProperty
newZeroEventProperty = IO EventProperty -> m EventProperty
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventProperty -> m EventProperty)
-> IO EventProperty -> m EventProperty
forall a b. (a -> b) -> a -> b
$ IO (Ptr EventProperty)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr EventProperty)
-> (Ptr EventProperty -> IO EventProperty) -> IO EventProperty
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventProperty -> EventProperty)
-> Ptr EventProperty -> IO EventProperty
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventProperty -> EventProperty
EventProperty

instance tag ~ 'AttrSet => Constructible EventProperty tag where
    new :: (ManagedPtr EventProperty -> EventProperty)
-> [AttrOp EventProperty tag] -> m EventProperty
new _ attrs :: [AttrOp EventProperty tag]
attrs = do
        EventProperty
o <- m EventProperty
forall (m :: * -> *). MonadIO m => m EventProperty
newZeroEventProperty
        EventProperty -> [AttrOp EventProperty 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set EventProperty
o [AttrOp EventProperty tag]
[AttrOp EventProperty 'AttrSet]
attrs
        EventProperty -> m EventProperty
forall (m :: * -> *) a. Monad m => a -> m a
return EventProperty
o


-- | A convenience alias for `Nothing` :: `Maybe` `EventProperty`.
noEventProperty :: Maybe EventProperty
noEventProperty :: Maybe EventProperty
noEventProperty = Maybe EventProperty
forall a. Maybe a
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' eventProperty #type
-- @
getEventPropertyType :: MonadIO m => EventProperty -> m Gdk.Enums.EventType
getEventPropertyType :: EventProperty -> m EventType
getEventPropertyType s :: EventProperty
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
$ EventProperty
-> (Ptr EventProperty -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO EventType) -> IO EventType)
-> (Ptr EventProperty -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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' eventProperty [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPropertyType :: MonadIO m => EventProperty -> Gdk.Enums.EventType -> m ()
setEventPropertyType :: EventProperty -> EventType -> m ()
setEventPropertyType s :: EventProperty
s val :: 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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
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 EventProperty
ptr Ptr EventProperty -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CInt
val' :: CInt)

#if defined(ENABLE_OVERLOADING)
data EventPropertyTypeFieldInfo
instance AttrInfo EventPropertyTypeFieldInfo where
    type AttrBaseTypeConstraint EventPropertyTypeFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPropertyTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrTransferTypeConstraint EventPropertyTypeFieldInfo = (~)Gdk.Enums.EventType
    type AttrTransferType EventPropertyTypeFieldInfo = Gdk.Enums.EventType
    type AttrGetType EventPropertyTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventPropertyTypeFieldInfo = "type"
    type AttrOrigin EventPropertyTypeFieldInfo = EventProperty
    attrGet = getEventPropertyType
    attrSet = setEventPropertyType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventProperty_type :: AttrLabelProxy "type"
eventProperty_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' eventProperty #window
-- @
getEventPropertyWindow :: MonadIO m => EventProperty -> m (Maybe Gdk.Window.Window)
getEventPropertyWindow :: EventProperty -> m (Maybe Window)
getEventPropertyWindow s :: EventProperty
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
$ EventProperty
-> (Ptr EventProperty -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventProperty -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ \val' :: 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' eventProperty [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPropertyWindow :: MonadIO m => EventProperty -> Ptr Gdk.Window.Window -> m ()
setEventPropertyWindow :: EventProperty -> Ptr Window -> m ()
setEventPropertyWindow s :: EventProperty
s val :: 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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
-- @
clearEventPropertyWindow :: MonadIO m => EventProperty -> m ()
clearEventPropertyWindow :: EventProperty -> m ()
clearEventPropertyWindow s :: EventProperty
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Window
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Window.Window)

#if defined(ENABLE_OVERLOADING)
data EventPropertyWindowFieldInfo
instance AttrInfo EventPropertyWindowFieldInfo where
    type AttrBaseTypeConstraint EventPropertyWindowFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventPropertyWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventPropertyWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventPropertyWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventPropertyWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventPropertyWindowFieldInfo = "window"
    type AttrOrigin EventPropertyWindowFieldInfo = EventProperty
    attrGet = getEventPropertyWindow
    attrSet = setEventPropertyWindow
    attrConstruct = undefined
    attrClear = clearEventPropertyWindow
    attrTransfer _ v = do
        return v

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

#if defined(ENABLE_OVERLOADING)
data EventPropertySendEventFieldInfo
instance AttrInfo EventPropertySendEventFieldInfo where
    type AttrBaseTypeConstraint EventPropertySendEventFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertySendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPropertySendEventFieldInfo = (~) Int8
    type AttrTransferTypeConstraint EventPropertySendEventFieldInfo = (~)Int8
    type AttrTransferType EventPropertySendEventFieldInfo = Int8
    type AttrGetType EventPropertySendEventFieldInfo = Int8
    type AttrLabel EventPropertySendEventFieldInfo = "send_event"
    type AttrOrigin EventPropertySendEventFieldInfo = EventProperty
    attrGet = getEventPropertySendEvent
    attrSet = setEventPropertySendEvent
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventProperty_sendEvent :: AttrLabelProxy "sendEvent"
eventProperty_sendEvent = AttrLabelProxy

#endif


-- | Get the value of the “@atom@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventProperty #atom
-- @
getEventPropertyAtom :: MonadIO m => EventProperty -> m Gdk.Atom.Atom
getEventPropertyAtom :: EventProperty -> m Atom
getEventPropertyAtom s :: EventProperty
s = IO Atom -> m Atom
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Atom -> m Atom) -> IO Atom -> m Atom
forall a b. (a -> b) -> a -> b
$ EventProperty -> (Ptr EventProperty -> IO Atom) -> IO Atom
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO Atom) -> IO Atom)
-> (Ptr EventProperty -> IO Atom) -> IO Atom
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    let val :: Ptr Atom
val = Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr Atom
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: (Ptr Gdk.Atom.Atom)
    Atom
val' <- ((ManagedPtr Atom -> Atom) -> Ptr Atom -> IO Atom
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Atom -> Atom
Gdk.Atom.Atom) Ptr Atom
val
    Atom -> IO Atom
forall (m :: * -> *) a. Monad m => a -> m a
return Atom
val'

#if defined(ENABLE_OVERLOADING)
data EventPropertyAtomFieldInfo
instance AttrInfo EventPropertyAtomFieldInfo where
    type AttrBaseTypeConstraint EventPropertyAtomFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyAtomFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventPropertyAtomFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrTransferTypeConstraint EventPropertyAtomFieldInfo = (~)(Ptr Gdk.Atom.Atom)
    type AttrTransferType EventPropertyAtomFieldInfo = (Ptr Gdk.Atom.Atom)
    type AttrGetType EventPropertyAtomFieldInfo = Gdk.Atom.Atom
    type AttrLabel EventPropertyAtomFieldInfo = "atom"
    type AttrOrigin EventPropertyAtomFieldInfo = EventProperty
    attrGet = getEventPropertyAtom
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined

eventProperty_atom :: AttrLabelProxy "atom"
eventProperty_atom = 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' eventProperty #time
-- @
getEventPropertyTime :: MonadIO m => EventProperty -> m Word32
getEventPropertyTime :: EventProperty -> m Word32
getEventPropertyTime s :: EventProperty
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
$ EventProperty -> (Ptr EventProperty -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO Word32) -> IO Word32)
-> (Ptr EventProperty -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: 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' eventProperty [ #time 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPropertyTime :: MonadIO m => EventProperty -> Word32 -> m ()
setEventPropertyTime :: EventProperty -> Word32 -> m ()
setEventPropertyTime s :: EventProperty
s val :: 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
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data EventPropertyTimeFieldInfo
instance AttrInfo EventPropertyTimeFieldInfo where
    type AttrBaseTypeConstraint EventPropertyTimeFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPropertyTimeFieldInfo = (~) Word32
    type AttrTransferTypeConstraint EventPropertyTimeFieldInfo = (~)Word32
    type AttrTransferType EventPropertyTimeFieldInfo = Word32
    type AttrGetType EventPropertyTimeFieldInfo = Word32
    type AttrLabel EventPropertyTimeFieldInfo = "time"
    type AttrOrigin EventPropertyTimeFieldInfo = EventProperty
    attrGet = getEventPropertyTime
    attrSet = setEventPropertyTime
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventProperty_time :: AttrLabelProxy "time"
eventProperty_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' eventProperty #state
-- @
getEventPropertyState :: MonadIO m => EventProperty -> m Gdk.Enums.PropertyState
getEventPropertyState :: EventProperty -> m PropertyState
getEventPropertyState s :: EventProperty
s = IO PropertyState -> m PropertyState
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyState -> m PropertyState)
-> IO PropertyState -> m PropertyState
forall a b. (a -> b) -> a -> b
$ EventProperty
-> (Ptr EventProperty -> IO PropertyState) -> IO PropertyState
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO PropertyState) -> IO PropertyState)
-> (Ptr EventProperty -> IO PropertyState) -> IO PropertyState
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36) :: IO CUInt
    let val' :: PropertyState
val' = (Int -> PropertyState
forall a. Enum a => Int -> a
toEnum (Int -> PropertyState) -> (CUInt -> Int) -> CUInt -> PropertyState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    PropertyState -> IO PropertyState
forall (m :: * -> *) a. Monad m => a -> m a
return PropertyState
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' eventProperty [ #state 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPropertyState :: MonadIO m => EventProperty -> Gdk.Enums.PropertyState -> m ()
setEventPropertyState :: EventProperty -> PropertyState -> m ()
setEventPropertyState s :: EventProperty
s val :: PropertyState
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventProperty -> (Ptr EventProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventProperty
s ((Ptr EventProperty -> IO ()) -> IO ())
-> (Ptr EventProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventProperty
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PropertyState -> Int) -> PropertyState -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PropertyState -> Int
forall a. Enum a => a -> Int
fromEnum) PropertyState
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventProperty
ptr Ptr EventProperty -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data EventPropertyStateFieldInfo
instance AttrInfo EventPropertyStateFieldInfo where
    type AttrBaseTypeConstraint EventPropertyStateFieldInfo = (~) EventProperty
    type AttrAllowedOps EventPropertyStateFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPropertyStateFieldInfo = (~) Gdk.Enums.PropertyState
    type AttrTransferTypeConstraint EventPropertyStateFieldInfo = (~)Gdk.Enums.PropertyState
    type AttrTransferType EventPropertyStateFieldInfo = Gdk.Enums.PropertyState
    type AttrGetType EventPropertyStateFieldInfo = Gdk.Enums.PropertyState
    type AttrLabel EventPropertyStateFieldInfo = "state"
    type AttrOrigin EventPropertyStateFieldInfo = EventProperty
    attrGet = getEventPropertyState
    attrSet = setEventPropertyState
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventProperty_state :: AttrLabelProxy "state"
eventProperty_state = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventProperty
type instance O.AttributeList EventProperty = EventPropertyAttributeList
type EventPropertyAttributeList = ('[ '("type", EventPropertyTypeFieldInfo), '("window", EventPropertyWindowFieldInfo), '("sendEvent", EventPropertySendEventFieldInfo), '("atom", EventPropertyAtomFieldInfo), '("time", EventPropertyTimeFieldInfo), '("state", EventPropertyStateFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveEventPropertyMethod t EventProperty, O.MethodInfo info EventProperty p) => OL.IsLabel t (EventProperty -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif