{- |
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 setting is modified.
-}

module GI.Gdk.Structs.EventSetting
    ( 

-- * Exported types
    EventSetting(..)                        ,
    newZeroEventSetting                     ,
    noEventSetting                          ,


 -- * Properties
-- ** action #attr:action#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    eventSetting_action                     ,
#endif
    getEventSettingAction                   ,
    setEventSettingAction                   ,


-- ** name #attr:name#
    clearEventSettingName                   ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    eventSetting_name                       ,
#endif
    getEventSettingName                     ,
    setEventSettingName                     ,


-- ** sendEvent #attr:sendEvent#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    eventSetting_sendEvent                  ,
#endif
    getEventSettingSendEvent                ,
    setEventSettingSendEvent                ,


-- ** type #attr:type#
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    eventSetting_type                       ,
#endif
    getEventSettingType                     ,
    setEventSettingType                     ,


-- ** window #attr:window#
    clearEventSettingWindow                 ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    eventSetting_window                     ,
#endif
    getEventSettingWindow                   ,
    setEventSettingWindow                   ,




    ) 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.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

newtype EventSetting = EventSetting (ManagedPtr EventSetting)
instance WrappedPtr EventSetting where
    wrappedPtrCalloc = callocBytes 32
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 32 >=> wrapPtr EventSetting)
    wrappedPtrFree = Just ptr_to_g_free

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

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


noEventSetting :: Maybe EventSetting
noEventSetting = Nothing

getEventSettingType :: MonadIO m => EventSetting -> m Gdk.Enums.EventType
getEventSettingType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setEventSettingType :: MonadIO m => EventSetting -> Gdk.Enums.EventType -> m ()
setEventSettingType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data EventSettingTypeFieldInfo
instance AttrInfo EventSettingTypeFieldInfo where
    type AttrAllowedOps EventSettingTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventSettingTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrBaseTypeConstraint EventSettingTypeFieldInfo = (~) EventSetting
    type AttrGetType EventSettingTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventSettingTypeFieldInfo = "type"
    type AttrOrigin EventSettingTypeFieldInfo = EventSetting
    attrGet _ = getEventSettingType
    attrSet _ = setEventSettingType
    attrConstruct = undefined
    attrClear _ = undefined

eventSetting_type :: AttrLabelProxy "type"
eventSetting_type = AttrLabelProxy

#endif


getEventSettingWindow :: MonadIO m => EventSetting -> m (Maybe Gdk.Window.Window)
getEventSettingWindow 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

setEventSettingWindow :: MonadIO m => EventSetting -> Ptr Gdk.Window.Window -> m ()
setEventSettingWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)

clearEventSettingWindow :: MonadIO m => EventSetting -> m ()
clearEventSettingWindow s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data EventSettingWindowFieldInfo
instance AttrInfo EventSettingWindowFieldInfo where
    type AttrAllowedOps EventSettingWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventSettingWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrBaseTypeConstraint EventSettingWindowFieldInfo = (~) EventSetting
    type AttrGetType EventSettingWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventSettingWindowFieldInfo = "window"
    type AttrOrigin EventSettingWindowFieldInfo = EventSetting
    attrGet _ = getEventSettingWindow
    attrSet _ = setEventSettingWindow
    attrConstruct = undefined
    attrClear _ = clearEventSettingWindow

eventSetting_window :: AttrLabelProxy "window"
eventSetting_window = AttrLabelProxy

#endif


getEventSettingSendEvent :: MonadIO m => EventSetting -> m Int8
getEventSettingSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int8
    return val

setEventSettingSendEvent :: MonadIO m => EventSetting -> Int8 -> m ()
setEventSettingSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int8)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data EventSettingSendEventFieldInfo
instance AttrInfo EventSettingSendEventFieldInfo where
    type AttrAllowedOps EventSettingSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventSettingSendEventFieldInfo = (~) Int8
    type AttrBaseTypeConstraint EventSettingSendEventFieldInfo = (~) EventSetting
    type AttrGetType EventSettingSendEventFieldInfo = Int8
    type AttrLabel EventSettingSendEventFieldInfo = "send_event"
    type AttrOrigin EventSettingSendEventFieldInfo = EventSetting
    attrGet _ = getEventSettingSendEvent
    attrSet _ = setEventSettingSendEvent
    attrConstruct = undefined
    attrClear _ = undefined

eventSetting_sendEvent :: AttrLabelProxy "sendEvent"
eventSetting_sendEvent = AttrLabelProxy

#endif


getEventSettingAction :: MonadIO m => EventSetting -> m Gdk.Enums.SettingAction
getEventSettingAction s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setEventSettingAction :: MonadIO m => EventSetting -> Gdk.Enums.SettingAction -> m ()
setEventSettingAction s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 20) (val' :: CUInt)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data EventSettingActionFieldInfo
instance AttrInfo EventSettingActionFieldInfo where
    type AttrAllowedOps EventSettingActionFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventSettingActionFieldInfo = (~) Gdk.Enums.SettingAction
    type AttrBaseTypeConstraint EventSettingActionFieldInfo = (~) EventSetting
    type AttrGetType EventSettingActionFieldInfo = Gdk.Enums.SettingAction
    type AttrLabel EventSettingActionFieldInfo = "action"
    type AttrOrigin EventSettingActionFieldInfo = EventSetting
    attrGet _ = getEventSettingAction
    attrSet _ = setEventSettingAction
    attrConstruct = undefined
    attrClear _ = undefined

eventSetting_action :: AttrLabelProxy "action"
eventSetting_action = AttrLabelProxy

#endif


getEventSettingName :: MonadIO m => EventSetting -> m (Maybe T.Text)
getEventSettingName s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

setEventSettingName :: MonadIO m => EventSetting -> CString -> m ()
setEventSettingName s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: CString)

clearEventSettingName :: MonadIO m => EventSetting -> m ()
clearEventSettingName s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data EventSettingNameFieldInfo
instance AttrInfo EventSettingNameFieldInfo where
    type AttrAllowedOps EventSettingNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventSettingNameFieldInfo = (~) CString
    type AttrBaseTypeConstraint EventSettingNameFieldInfo = (~) EventSetting
    type AttrGetType EventSettingNameFieldInfo = Maybe T.Text
    type AttrLabel EventSettingNameFieldInfo = "name"
    type AttrOrigin EventSettingNameFieldInfo = EventSetting
    attrGet _ = getEventSettingName
    attrSet _ = setEventSettingName
    attrConstruct = undefined
    attrClear _ = clearEventSettingName

eventSetting_name :: AttrLabelProxy "name"
eventSetting_name = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList EventSetting
type instance O.AttributeList EventSetting = EventSettingAttributeList
type EventSettingAttributeList = ('[ '("type", EventSettingTypeFieldInfo), '("window", EventSettingWindowFieldInfo), '("sendEvent", EventSettingSendEventFieldInfo), '("action", EventSettingActionFieldInfo), '("name", EventSettingNameFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolveEventSettingMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventSettingMethod l o = O.MethodResolutionFailed l o

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

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