{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Generated when all or part of a window becomes visible and needs to be
-- redrawn.

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

module GI.Gdk.Structs.EventExpose
    ( 

-- * Exported types
    EventExpose(..)                         ,
    newZeroEventExpose                      ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveEventExposeMethod                ,
#endif




 -- * Properties
-- ** area #attr:area#
-- | bounding box of /@region@/.

#if defined(ENABLE_OVERLOADING)
    eventExpose_area                        ,
#endif
    getEventExposeArea                      ,


-- ** count #attr:count#
-- | the number of contiguous 'GI.Gdk.Enums.EventTypeExpose' events following this one.
--   The only use for this is “exposure compression”, i.e. handling all
--   contiguous 'GI.Gdk.Enums.EventTypeExpose' events in one go, though GDK performs some
--   exposure compression so this is not normally needed.

#if defined(ENABLE_OVERLOADING)
    eventExpose_count                       ,
#endif
    getEventExposeCount                     ,
    setEventExposeCount                     ,


-- ** region #attr:region#
-- | the region that needs to be redrawn.

    clearEventExposeRegion                  ,
#if defined(ENABLE_OVERLOADING)
    eventExpose_region                      ,
#endif
    getEventExposeRegion                    ,
    setEventExposeRegion                    ,


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

#if defined(ENABLE_OVERLOADING)
    eventExpose_sendEvent                   ,
#endif
    getEventExposeSendEvent                 ,
    setEventExposeSendEvent                 ,


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

#if defined(ENABLE_OVERLOADING)
    eventExpose_type                        ,
#endif
    getEventExposeType                      ,
    setEventExposeType                      ,


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

    clearEventExposeWindow                  ,
#if defined(ENABLE_OVERLOADING)
    eventExpose_window                      ,
#endif
    getEventExposeWindow                    ,
    setEventExposeWindow                    ,




    ) 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.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.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 GI.Cairo.Structs.Region as Cairo.Region
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.Rectangle as Gdk.Rectangle

-- | Memory-managed wrapper type.
newtype EventExpose = EventExpose (SP.ManagedPtr EventExpose)
    deriving (EventExpose -> EventExpose -> Bool
(EventExpose -> EventExpose -> Bool)
-> (EventExpose -> EventExpose -> Bool) -> Eq EventExpose
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventExpose -> EventExpose -> Bool
$c/= :: EventExpose -> EventExpose -> Bool
== :: EventExpose -> EventExpose -> Bool
$c== :: EventExpose -> EventExpose -> Bool
Eq)

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

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


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

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

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

eventExpose_type :: AttrLabelProxy "type"
eventExpose_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' eventExpose #window
-- @
getEventExposeWindow :: MonadIO m => EventExpose -> m (Maybe Gdk.Window.Window)
getEventExposeWindow :: EventExpose -> m (Maybe Window)
getEventExposeWindow EventExpose
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
$ EventExpose
-> (Ptr EventExpose -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventExpose
s ((Ptr EventExpose -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventExpose -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr EventExpose
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventExpose
ptr Ptr EventExpose -> 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' eventExpose [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventExposeWindow :: MonadIO m => EventExpose -> Ptr Gdk.Window.Window -> m ()
setEventExposeWindow :: EventExpose -> Ptr Window -> m ()
setEventExposeWindow EventExpose
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
$ EventExpose -> (Ptr EventExpose -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventExpose
s ((Ptr EventExpose -> IO ()) -> IO ())
-> (Ptr EventExpose -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventExpose
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventExpose
ptr Ptr EventExpose -> 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
-- @
clearEventExposeWindow :: MonadIO m => EventExpose -> m ()
clearEventExposeWindow :: EventExpose -> m ()
clearEventExposeWindow EventExpose
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventExpose -> (Ptr EventExpose -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventExpose
s ((Ptr EventExpose -> IO ()) -> IO ())
-> (Ptr EventExpose -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventExpose
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventExpose
ptr Ptr EventExpose -> 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 EventExposeWindowFieldInfo
instance AttrInfo EventExposeWindowFieldInfo where
    type AttrBaseTypeConstraint EventExposeWindowFieldInfo = (~) EventExpose
    type AttrAllowedOps EventExposeWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventExposeWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventExposeWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventExposeWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventExposeWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventExposeWindowFieldInfo = "window"
    type AttrOrigin EventExposeWindowFieldInfo = EventExpose
    attrGet = getEventExposeWindow
    attrSet = setEventExposeWindow
    attrConstruct = undefined
    attrClear = clearEventExposeWindow
    attrTransfer _ v = do
        return v

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

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

eventExpose_sendEvent :: AttrLabelProxy "sendEvent"
eventExpose_sendEvent = AttrLabelProxy

#endif


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

#if defined(ENABLE_OVERLOADING)
data EventExposeAreaFieldInfo
instance AttrInfo EventExposeAreaFieldInfo where
    type AttrBaseTypeConstraint EventExposeAreaFieldInfo = (~) EventExpose
    type AttrAllowedOps EventExposeAreaFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventExposeAreaFieldInfo = (~) (Ptr Gdk.Rectangle.Rectangle)
    type AttrTransferTypeConstraint EventExposeAreaFieldInfo = (~)(Ptr Gdk.Rectangle.Rectangle)
    type AttrTransferType EventExposeAreaFieldInfo = (Ptr Gdk.Rectangle.Rectangle)
    type AttrGetType EventExposeAreaFieldInfo = Gdk.Rectangle.Rectangle
    type AttrLabel EventExposeAreaFieldInfo = "area"
    type AttrOrigin EventExposeAreaFieldInfo = EventExpose
    attrGet = getEventExposeArea
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined

eventExpose_area :: AttrLabelProxy "area"
eventExpose_area = AttrLabelProxy

#endif


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

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

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

#if defined(ENABLE_OVERLOADING)
data EventExposeRegionFieldInfo
instance AttrInfo EventExposeRegionFieldInfo where
    type AttrBaseTypeConstraint EventExposeRegionFieldInfo = (~) EventExpose
    type AttrAllowedOps EventExposeRegionFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventExposeRegionFieldInfo = (~) (Ptr Cairo.Region.Region)
    type AttrTransferTypeConstraint EventExposeRegionFieldInfo = (~)(Ptr Cairo.Region.Region)
    type AttrTransferType EventExposeRegionFieldInfo = (Ptr Cairo.Region.Region)
    type AttrGetType EventExposeRegionFieldInfo = Maybe Cairo.Region.Region
    type AttrLabel EventExposeRegionFieldInfo = "region"
    type AttrOrigin EventExposeRegionFieldInfo = EventExpose
    attrGet = getEventExposeRegion
    attrSet = setEventExposeRegion
    attrConstruct = undefined
    attrClear = clearEventExposeRegion
    attrTransfer _ v = do
        return v

eventExpose_region :: AttrLabelProxy "region"
eventExpose_region = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data EventExposeCountFieldInfo
instance AttrInfo EventExposeCountFieldInfo where
    type AttrBaseTypeConstraint EventExposeCountFieldInfo = (~) EventExpose
    type AttrAllowedOps EventExposeCountFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventExposeCountFieldInfo = (~) Int32
    type AttrTransferTypeConstraint EventExposeCountFieldInfo = (~)Int32
    type AttrTransferType EventExposeCountFieldInfo = Int32
    type AttrGetType EventExposeCountFieldInfo = Int32
    type AttrLabel EventExposeCountFieldInfo = "count"
    type AttrOrigin EventExposeCountFieldInfo = EventExpose
    attrGet = getEventExposeCount
    attrSet = setEventExposeCount
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventExpose_count :: AttrLabelProxy "count"
eventExpose_count = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventExpose
type instance O.AttributeList EventExpose = EventExposeAttributeList
type EventExposeAttributeList = ('[ '("type", EventExposeTypeFieldInfo), '("window", EventExposeWindowFieldInfo), '("sendEvent", EventExposeSendEventFieldInfo), '("area", EventExposeAreaFieldInfo), '("region", EventExposeRegionFieldInfo), '("count", EventExposeCountFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif