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

Generated when all or part of a window becomes visible and needs to be
redrawn.
-}

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

module GI.Gdk.Structs.EventExpose
    (

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


 -- * Properties
-- ** area #attr:area#
{- | bounding box of /@region@/.
-}
#if 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 ENABLE_OVERLOADING
    eventExpose_count                       ,
#endif
    getEventExposeCount                     ,
    setEventExposeCount                     ,


-- ** region #attr:region#
{- | the region that needs to be redrawn.
-}
    clearEventExposeRegion                  ,
#if ENABLE_OVERLOADING
    eventExpose_region                      ,
#endif
    getEventExposeRegion                    ,
    setEventExposeRegion                    ,


-- ** sendEvent #attr:sendEvent#
{- | 'True' if the event was sent explicitly.
-}
#if 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 ENABLE_OVERLOADING
    eventExpose_type                        ,
#endif
    getEventExposeType                      ,
    setEventExposeType                      ,


-- ** window #attr:window#
{- | the window which received the event.
-}
    clearEventExposeWindow                  ,
#if 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import 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 (ManagedPtr EventExpose)
instance WrappedPtr EventExpose where
    wrappedPtrCalloc = callocBytes 56
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 56 >=> wrapPtr EventExpose)
    wrappedPtrFree = Just ptr_to_g_free

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `EventExpose`.
noEventExpose :: Maybe EventExpose
noEventExpose = 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' eventExpose #type
@
-}
getEventExposeType :: MonadIO m => EventExpose -> m Gdk.Enums.EventType
getEventExposeType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' eventExpose [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventExposeType :: MonadIO m => EventExpose -> Gdk.Enums.EventType -> m ()
setEventExposeType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CInt)

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr Gdk.Window.Window)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newObject Gdk.Window.Window) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' eventExpose [ #window 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventExposeWindow :: MonadIO m => EventExpose -> Ptr Gdk.Window.Window -> m ()
setEventExposeWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)

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

@
'Data.GI.Base.Attributes.clear' #window
@
-}
clearEventExposeWindow :: MonadIO m => EventExpose -> m ()
clearEventExposeWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)

#if ENABLE_OVERLOADING
data EventExposeWindowFieldInfo
instance AttrInfo EventExposeWindowFieldInfo where
    type AttrAllowedOps EventExposeWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventExposeWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventExposeWindowFieldInfo = (~) EventExpose
    type AttrGetType EventExposeWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventExposeWindowFieldInfo = "window"
    type AttrOrigin EventExposeWindowFieldInfo = EventExpose
    attrGet _ = getEventExposeWindow
    attrSet _ = setEventExposeWindow
    attrConstruct = undefined
    attrClear _ = clearEventExposeWindow

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int8
    return val

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

@
'Data.GI.Base.Attributes.set' eventExpose [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventExposeSendEvent :: MonadIO m => EventExpose -> Int8 -> m ()
setEventExposeSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int8)

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 20 :: (Ptr Gdk.Rectangle.Rectangle)
    val' <- (newBoxed Gdk.Rectangle.Rectangle) val
    return val'

#if ENABLE_OVERLOADING
data EventExposeAreaFieldInfo
instance AttrInfo EventExposeAreaFieldInfo where
    type AttrAllowedOps EventExposeAreaFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventExposeAreaFieldInfo = (~) (Ptr Gdk.Rectangle.Rectangle)
    type AttrBaseTypeConstraint EventExposeAreaFieldInfo = (~) EventExpose
    type AttrGetType EventExposeAreaFieldInfo = Gdk.Rectangle.Rectangle
    type AttrLabel EventExposeAreaFieldInfo = "area"
    type AttrOrigin EventExposeAreaFieldInfo = EventExpose
    attrGet _ = getEventExposeArea
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = 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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO (Ptr Cairo.Region.Region)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed Cairo.Region.Region) val'
        return val''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (FP.nullPtr :: Ptr Cairo.Region.Region)

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

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO Int32
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (val :: Int32)

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

eventExpose_count :: AttrLabelProxy "count"
eventExpose_count = AttrLabelProxy

#endif



#if 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 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 (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif

#endif