{- |
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 during 'GI.Gdk.Enums.InputSourceTabletPad' mode switches in a group.

/Since: 3.22/
-}

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

module GI.Gdk.Structs.EventPadGroupMode
    (

-- * Exported types
    EventPadGroupMode(..)                   ,
    newZeroEventPadGroupMode                ,
    noEventPadGroupMode                     ,


 -- * Properties
-- ** group #attr:group#
{- | the pad group that is switching mode. A 'GI.Gdk.Enums.InputSourceTabletPad'
  device may have one or more groups containing a set of buttons\/rings\/strips
  each.
-}
#if ENABLE_OVERLOADING
    eventPadGroupMode_group                 ,
#endif
    getEventPadGroupModeGroup               ,
    setEventPadGroupModeGroup               ,


-- ** mode #attr:mode#
{- | The new mode of /@group@/. Different groups in a 'GI.Gdk.Enums.InputSourceTabletPad'
  device may have different current modes.
-}
#if ENABLE_OVERLOADING
    eventPadGroupMode_mode                  ,
#endif
    getEventPadGroupModeMode                ,
    setEventPadGroupModeMode                ,


-- ** sendEvent #attr:sendEvent#
{- | 'True' if the event was sent explicitly.
-}
#if ENABLE_OVERLOADING
    eventPadGroupMode_sendEvent             ,
#endif
    getEventPadGroupModeSendEvent           ,
    setEventPadGroupModeSendEvent           ,


-- ** time #attr:time#
{- | the time of the event in milliseconds.
-}
#if ENABLE_OVERLOADING
    eventPadGroupMode_time                  ,
#endif
    getEventPadGroupModeTime                ,
    setEventPadGroupModeTime                ,


-- ** type #attr:type#
{- | the type of the event ('GI.Gdk.Enums.EventTypePadGroupMode').
-}
#if ENABLE_OVERLOADING
    eventPadGroupMode_type                  ,
#endif
    getEventPadGroupModeType                ,
    setEventPadGroupModeType                ,


-- ** window #attr:window#
{- | the window which received the event.
-}
    clearEventPadGroupModeWindow            ,
#if ENABLE_OVERLOADING
    eventPadGroupMode_window                ,
#endif
    getEventPadGroupModeWindow              ,
    setEventPadGroupModeWindow              ,




    ) 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

-- | Memory-managed wrapper type.
newtype EventPadGroupMode = EventPadGroupMode (ManagedPtr EventPadGroupMode)
instance WrappedPtr EventPadGroupMode where
    wrappedPtrCalloc = callocBytes 32
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 32 >=> wrapPtr EventPadGroupMode)
    wrappedPtrFree = Just ptr_to_g_free

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

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


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

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

eventPadGroupMode_type :: AttrLabelProxy "type"
eventPadGroupMode_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' eventPadGroupMode #window
@
-}
getEventPadGroupModeWindow :: MonadIO m => EventPadGroupMode -> m (Maybe Gdk.Window.Window)
getEventPadGroupModeWindow 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' eventPadGroupMode [ #window 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventPadGroupModeWindow :: MonadIO m => EventPadGroupMode -> Ptr Gdk.Window.Window -> m ()
setEventPadGroupModeWindow 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
@
-}
clearEventPadGroupModeWindow :: MonadIO m => EventPadGroupMode -> m ()
clearEventPadGroupModeWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)

#if ENABLE_OVERLOADING
data EventPadGroupModeWindowFieldInfo
instance AttrInfo EventPadGroupModeWindowFieldInfo where
    type AttrAllowedOps EventPadGroupModeWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventPadGroupModeWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventPadGroupModeWindowFieldInfo = (~) EventPadGroupMode
    type AttrGetType EventPadGroupModeWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventPadGroupModeWindowFieldInfo = "window"
    type AttrOrigin EventPadGroupModeWindowFieldInfo = EventPadGroupMode
    attrGet _ = getEventPadGroupModeWindow
    attrSet _ = setEventPadGroupModeWindow
    attrConstruct = undefined
    attrClear _ = clearEventPadGroupModeWindow

eventPadGroupMode_window :: AttrLabelProxy "window"
eventPadGroupMode_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' eventPadGroupMode #sendEvent
@
-}
getEventPadGroupModeSendEvent :: MonadIO m => EventPadGroupMode -> m Int8
getEventPadGroupModeSendEvent 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' eventPadGroupMode [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventPadGroupModeSendEvent :: MonadIO m => EventPadGroupMode -> Int8 -> m ()
setEventPadGroupModeSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int8)

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

eventPadGroupMode_sendEvent :: AttrLabelProxy "sendEvent"
eventPadGroupMode_sendEvent = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventPadGroupMode #time
@
-}
getEventPadGroupModeTime :: MonadIO m => EventPadGroupMode -> m Word32
getEventPadGroupModeTime s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: 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' eventPadGroupMode [ #time 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventPadGroupModeTime :: MonadIO m => EventPadGroupMode -> Word32 -> m ()
setEventPadGroupModeTime s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 20) (val :: Word32)

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

eventPadGroupMode_time :: AttrLabelProxy "time"
eventPadGroupMode_time = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventPadGroupMode #group
@
-}
getEventPadGroupModeGroup :: MonadIO m => EventPadGroupMode -> m Word32
getEventPadGroupModeGroup s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' eventPadGroupMode [ #group 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventPadGroupModeGroup :: MonadIO m => EventPadGroupMode -> Word32 -> m ()
setEventPadGroupModeGroup s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Word32)

#if ENABLE_OVERLOADING
data EventPadGroupModeGroupFieldInfo
instance AttrInfo EventPadGroupModeGroupFieldInfo where
    type AttrAllowedOps EventPadGroupModeGroupFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPadGroupModeGroupFieldInfo = (~) Word32
    type AttrBaseTypeConstraint EventPadGroupModeGroupFieldInfo = (~) EventPadGroupMode
    type AttrGetType EventPadGroupModeGroupFieldInfo = Word32
    type AttrLabel EventPadGroupModeGroupFieldInfo = "group"
    type AttrOrigin EventPadGroupModeGroupFieldInfo = EventPadGroupMode
    attrGet _ = getEventPadGroupModeGroup
    attrSet _ = setEventPadGroupModeGroup
    attrConstruct = undefined
    attrClear _ = undefined

eventPadGroupMode_group :: AttrLabelProxy "group"
eventPadGroupMode_group = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' eventPadGroupMode #mode
@
-}
getEventPadGroupModeMode :: MonadIO m => EventPadGroupMode -> m Word32
getEventPadGroupModeMode s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 28) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' eventPadGroupMode [ #mode 'Data.GI.Base.Attributes.:=' value ]
@
-}
setEventPadGroupModeMode :: MonadIO m => EventPadGroupMode -> Word32 -> m ()
setEventPadGroupModeMode s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 28) (val :: Word32)

#if ENABLE_OVERLOADING
data EventPadGroupModeModeFieldInfo
instance AttrInfo EventPadGroupModeModeFieldInfo where
    type AttrAllowedOps EventPadGroupModeModeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPadGroupModeModeFieldInfo = (~) Word32
    type AttrBaseTypeConstraint EventPadGroupModeModeFieldInfo = (~) EventPadGroupMode
    type AttrGetType EventPadGroupModeModeFieldInfo = Word32
    type AttrLabel EventPadGroupModeModeFieldInfo = "mode"
    type AttrOrigin EventPadGroupModeModeFieldInfo = EventPadGroupMode
    attrGet _ = getEventPadGroupModeMode
    attrSet _ = setEventPadGroupModeMode
    attrConstruct = undefined
    attrClear _ = undefined

eventPadGroupMode_mode :: AttrLabelProxy "mode"
eventPadGroupMode_mode = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList EventPadGroupMode
type instance O.AttributeList EventPadGroupMode = EventPadGroupModeAttributeList
type EventPadGroupModeAttributeList = ('[ '("type", EventPadGroupModeTypeFieldInfo), '("window", EventPadGroupModeWindowFieldInfo), '("sendEvent", EventPadGroupModeSendEventFieldInfo), '("time", EventPadGroupModeTimeFieldInfo), '("group", EventPadGroupModeGroupFieldInfo), '("mode", EventPadGroupModeModeFieldInfo)] :: [(Symbol, *)])
#endif

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

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

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