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

Generated when a selection is requested or ownership of a selection
is taken over by another client application.
-}

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

module GI.Gdk.Structs.EventSelection
    (

-- * Exported types
    EventSelection(..)                      ,
    newZeroEventSelection                   ,
    noEventSelection                        ,


 -- * Properties
-- ** property #attr:property#
{- | the property in which to place the result of the conversion.
-}
#if ENABLE_OVERLOADING
    eventSelection_property                 ,
#endif
    getEventSelectionProperty               ,


-- ** requestor #attr:requestor#
{- | the window on which to place /@property@/ or 'Nothing' if none.
-}
    clearEventSelectionRequestor            ,
#if ENABLE_OVERLOADING
    eventSelection_requestor                ,
#endif
    getEventSelectionRequestor              ,
    setEventSelectionRequestor              ,


-- ** selection #attr:selection#
{- | the selection.
-}
#if ENABLE_OVERLOADING
    eventSelection_selection                ,
#endif
    getEventSelectionSelection              ,


-- ** sendEvent #attr:sendEvent#
{- | 'True' if the event was sent explicitly.
-}
#if ENABLE_OVERLOADING
    eventSelection_sendEvent                ,
#endif
    getEventSelectionSendEvent              ,
    setEventSelectionSendEvent              ,


-- ** target #attr:target#
{- | the target to which the selection should be converted.
-}
#if ENABLE_OVERLOADING
    eventSelection_target                   ,
#endif
    getEventSelectionTarget                 ,


-- ** time #attr:time#
{- | the time of the event in milliseconds.
-}
#if ENABLE_OVERLOADING
    eventSelection_time                     ,
#endif
    getEventSelectionTime                   ,
    setEventSelectionTime                   ,


-- ** type #attr:type#
{- | the type of the event ('GI.Gdk.Enums.EventTypeSelectionClear',
  'GI.Gdk.Enums.EventTypeSelectionNotify' or 'GI.Gdk.Enums.EventTypeSelectionRequest').
-}
#if ENABLE_OVERLOADING
    eventSelection_type                     ,
#endif
    getEventSelectionType                   ,
    setEventSelectionType                   ,


-- ** window #attr:window#
{- | the window which received the event.
-}
    clearEventSelectionWindow               ,
#if ENABLE_OVERLOADING
    eventSelection_window                   ,
#endif
    getEventSelectionWindow                 ,
    setEventSelectionWindow                 ,




    ) 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `EventSelection`.
noEventSelection :: Maybe EventSelection
noEventSelection = 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' eventSelection #type
@
-}
getEventSelectionType :: MonadIO m => EventSelection -> m Gdk.Enums.EventType
getEventSelectionType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    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' eventSelection [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventSelectionType :: MonadIO m => EventSelection -> Gdk.Enums.EventType -> m ()
setEventSelectionType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

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

eventSelection_type :: AttrLabelProxy "type"
eventSelection_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' eventSelection #window
@
-}
getEventSelectionWindow :: MonadIO m => EventSelection -> m (Maybe Gdk.Window.Window)
getEventSelectionWindow 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' eventSelection [ #window 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventSelectionWindow :: MonadIO m => EventSelection -> Ptr Gdk.Window.Window -> m ()
setEventSelectionWindow 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
@
-}
clearEventSelectionWindow :: MonadIO m => EventSelection -> m ()
clearEventSelectionWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)

#if ENABLE_OVERLOADING
data EventSelectionWindowFieldInfo
instance AttrInfo EventSelectionWindowFieldInfo where
    type AttrAllowedOps EventSelectionWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventSelectionWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventSelectionWindowFieldInfo = (~) EventSelection
    type AttrGetType EventSelectionWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventSelectionWindowFieldInfo = "window"
    type AttrOrigin EventSelectionWindowFieldInfo = EventSelection
    attrGet _ = getEventSelectionWindow
    attrSet _ = setEventSelectionWindow
    attrConstruct = undefined
    attrClear _ = clearEventSelectionWindow

eventSelection_window :: AttrLabelProxy "window"
eventSelection_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' eventSelection #sendEvent
@
-}
getEventSelectionSendEvent :: MonadIO m => EventSelection -> m Int8
getEventSelectionSendEvent 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' eventSelection [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventSelectionSendEvent :: MonadIO m => EventSelection -> Int8 -> m ()
setEventSelectionSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int8)

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

eventSelection_sendEvent :: AttrLabelProxy "sendEvent"
eventSelection_sendEvent = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventSelection #selection
@
-}
getEventSelectionSelection :: MonadIO m => EventSelection -> m Gdk.Atom.Atom
getEventSelectionSelection s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 24 :: (Ptr Gdk.Atom.Atom)
    val' <- (newPtr Gdk.Atom.Atom) val
    return val'

#if ENABLE_OVERLOADING
data EventSelectionSelectionFieldInfo
instance AttrInfo EventSelectionSelectionFieldInfo where
    type AttrAllowedOps EventSelectionSelectionFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventSelectionSelectionFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrBaseTypeConstraint EventSelectionSelectionFieldInfo = (~) EventSelection
    type AttrGetType EventSelectionSelectionFieldInfo = Gdk.Atom.Atom
    type AttrLabel EventSelectionSelectionFieldInfo = "selection"
    type AttrOrigin EventSelectionSelectionFieldInfo = EventSelection
    attrGet _ = getEventSelectionSelection
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

eventSelection_selection :: AttrLabelProxy "selection"
eventSelection_selection = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventSelection #target
@
-}
getEventSelectionTarget :: MonadIO m => EventSelection -> m Gdk.Atom.Atom
getEventSelectionTarget s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 32 :: (Ptr Gdk.Atom.Atom)
    val' <- (newPtr Gdk.Atom.Atom) val
    return val'

#if ENABLE_OVERLOADING
data EventSelectionTargetFieldInfo
instance AttrInfo EventSelectionTargetFieldInfo where
    type AttrAllowedOps EventSelectionTargetFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventSelectionTargetFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrBaseTypeConstraint EventSelectionTargetFieldInfo = (~) EventSelection
    type AttrGetType EventSelectionTargetFieldInfo = Gdk.Atom.Atom
    type AttrLabel EventSelectionTargetFieldInfo = "target"
    type AttrOrigin EventSelectionTargetFieldInfo = EventSelection
    attrGet _ = getEventSelectionTarget
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

eventSelection_target :: AttrLabelProxy "target"
eventSelection_target = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventSelection #property
@
-}
getEventSelectionProperty :: MonadIO m => EventSelection -> m Gdk.Atom.Atom
getEventSelectionProperty s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 40 :: (Ptr Gdk.Atom.Atom)
    val' <- (newPtr Gdk.Atom.Atom) val
    return val'

#if ENABLE_OVERLOADING
data EventSelectionPropertyFieldInfo
instance AttrInfo EventSelectionPropertyFieldInfo where
    type AttrAllowedOps EventSelectionPropertyFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint EventSelectionPropertyFieldInfo = (~) (Ptr Gdk.Atom.Atom)
    type AttrBaseTypeConstraint EventSelectionPropertyFieldInfo = (~) EventSelection
    type AttrGetType EventSelectionPropertyFieldInfo = Gdk.Atom.Atom
    type AttrLabel EventSelectionPropertyFieldInfo = "property"
    type AttrOrigin EventSelectionPropertyFieldInfo = EventSelection
    attrGet _ = getEventSelectionProperty
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

eventSelection_property :: AttrLabelProxy "property"
eventSelection_property = 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' eventSelection #time
@
-}
getEventSelectionTime :: MonadIO m => EventSelection -> m Word32
getEventSelectionTime s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO Word32
    return 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' eventSelection [ #time 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventSelectionTime :: MonadIO m => EventSelection -> Word32 -> m ()
setEventSelectionTime s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (val :: Word32)

#if ENABLE_OVERLOADING
data EventSelectionTimeFieldInfo
instance AttrInfo EventSelectionTimeFieldInfo where
    type AttrAllowedOps EventSelectionTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventSelectionTimeFieldInfo = (~) Word32
    type AttrBaseTypeConstraint EventSelectionTimeFieldInfo = (~) EventSelection
    type AttrGetType EventSelectionTimeFieldInfo = Word32
    type AttrLabel EventSelectionTimeFieldInfo = "time"
    type AttrOrigin EventSelectionTimeFieldInfo = EventSelection
    attrGet _ = getEventSelectionTime
    attrSet _ = setEventSelectionTime
    attrConstruct = undefined
    attrClear _ = undefined

eventSelection_time :: AttrLabelProxy "time"
eventSelection_time = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventSelection #requestor
@
-}
getEventSelectionRequestor :: MonadIO m => EventSelection -> m (Maybe Gdk.Window.Window)
getEventSelectionRequestor s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: 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 “@requestor@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' eventSelection [ #requestor 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventSelectionRequestor :: MonadIO m => EventSelection -> Ptr Gdk.Window.Window -> m ()
setEventSelectionRequestor s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (val :: Ptr Gdk.Window.Window)

{- |
Set the value of the “@requestor@” 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' #requestor
@
-}
clearEventSelectionRequestor :: MonadIO m => EventSelection -> m ()
clearEventSelectionRequestor s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (FP.nullPtr :: Ptr Gdk.Window.Window)

#if ENABLE_OVERLOADING
data EventSelectionRequestorFieldInfo
instance AttrInfo EventSelectionRequestorFieldInfo where
    type AttrAllowedOps EventSelectionRequestorFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventSelectionRequestorFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventSelectionRequestorFieldInfo = (~) EventSelection
    type AttrGetType EventSelectionRequestorFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventSelectionRequestorFieldInfo = "requestor"
    type AttrOrigin EventSelectionRequestorFieldInfo = EventSelection
    attrGet _ = getEventSelectionRequestor
    attrSet _ = setEventSelectionRequestor
    attrConstruct = undefined
    attrClear _ = clearEventSelectionRequestor

eventSelection_requestor :: AttrLabelProxy "requestor"
eventSelection_requestor = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList EventSelection
type instance O.AttributeList EventSelection = EventSelectionAttributeList
type EventSelectionAttributeList = ('[ '("type", EventSelectionTypeFieldInfo), '("window", EventSelectionWindowFieldInfo), '("sendEvent", EventSelectionSendEventFieldInfo), '("selection", EventSelectionSelectionFieldInfo), '("target", EventSelectionTargetFieldInfo), '("property", EventSelectionPropertyFieldInfo), '("time", EventSelectionTimeFieldInfo), '("requestor", EventSelectionRequestorFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveEventSelectionMethod t EventSelection, O.MethodInfo info EventSelection p) => O.IsLabelProxy t (EventSelection -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveEventSelectionMethod t EventSelection, O.MethodInfo info EventSelection p) => O.IsLabel t (EventSelection -> 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

#endif