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

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

module GI.Gdk.Structs.EventSetting
    ( 

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


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

#if defined(ENABLE_OVERLOADING)
    ResolveEventSettingMethod               ,
#endif




 -- * Properties
-- ** action #attr:action#
-- | what happened to the setting ('GI.Gdk.Enums.SettingActionNew',
--   'GI.Gdk.Enums.SettingActionChanged' or 'GI.Gdk.Enums.SettingActionDeleted').

#if defined(ENABLE_OVERLOADING)
    eventSetting_action                     ,
#endif
    getEventSettingAction                   ,
    setEventSettingAction                   ,


-- ** name #attr:name#
-- | the name of the setting.

    clearEventSettingName                   ,
#if defined(ENABLE_OVERLOADING)
    eventSetting_name                       ,
#endif
    getEventSettingName                     ,
    setEventSettingName                     ,


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

#if defined(ENABLE_OVERLOADING)
    eventSetting_sendEvent                  ,
#endif
    getEventSettingSendEvent                ,
    setEventSettingSendEvent                ,


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

#if defined(ENABLE_OVERLOADING)
    eventSetting_type                       ,
#endif
    getEventSettingType                     ,
    setEventSettingType                     ,


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

    clearEventSettingWindow                 ,
#if defined(ENABLE_OVERLOADING)
    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.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 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 {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window

-- | Memory-managed wrapper type.
newtype EventSetting = EventSetting (ManagedPtr EventSetting)
    deriving (EventSetting -> EventSetting -> Bool
(EventSetting -> EventSetting -> Bool)
-> (EventSetting -> EventSetting -> Bool) -> Eq EventSetting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventSetting -> EventSetting -> Bool
$c/= :: EventSetting -> EventSetting -> Bool
== :: EventSetting -> EventSetting -> Bool
$c== :: EventSetting -> EventSetting -> Bool
Eq)
instance WrappedPtr EventSetting where
    wrappedPtrCalloc :: IO (Ptr EventSetting)
wrappedPtrCalloc = Int -> IO (Ptr EventSetting)
forall a. Int -> IO (Ptr a)
callocBytes 32
    wrappedPtrCopy :: EventSetting -> IO EventSetting
wrappedPtrCopy = \p :: EventSetting
p -> EventSetting
-> (Ptr EventSetting -> IO EventSetting) -> IO EventSetting
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
p (Int -> Ptr EventSetting -> IO (Ptr EventSetting)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 32 (Ptr EventSetting -> IO (Ptr EventSetting))
-> (Ptr EventSetting -> IO EventSetting)
-> Ptr EventSetting
-> IO EventSetting
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventSetting -> EventSetting)
-> Ptr EventSetting -> IO EventSetting
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventSetting -> EventSetting
EventSetting)
    wrappedPtrFree :: Maybe (GDestroyNotify EventSetting)
wrappedPtrFree = GDestroyNotify EventSetting -> Maybe (GDestroyNotify EventSetting)
forall a. a -> Maybe a
Just GDestroyNotify EventSetting
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `EventSetting` struct initialized to zero.
newZeroEventSetting :: MonadIO m => m EventSetting
newZeroEventSetting :: m EventSetting
newZeroEventSetting = IO EventSetting -> m EventSetting
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventSetting -> m EventSetting)
-> IO EventSetting -> m EventSetting
forall a b. (a -> b) -> a -> b
$ IO (Ptr EventSetting)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr EventSetting)
-> (Ptr EventSetting -> IO EventSetting) -> IO EventSetting
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventSetting -> EventSetting)
-> Ptr EventSetting -> IO EventSetting
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventSetting -> EventSetting
EventSetting

instance tag ~ 'AttrSet => Constructible EventSetting tag where
    new :: (ManagedPtr EventSetting -> EventSetting)
-> [AttrOp EventSetting tag] -> m EventSetting
new _ attrs :: [AttrOp EventSetting tag]
attrs = do
        EventSetting
o <- m EventSetting
forall (m :: * -> *). MonadIO m => m EventSetting
newZeroEventSetting
        EventSetting -> [AttrOp EventSetting 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set EventSetting
o [AttrOp EventSetting tag]
[AttrOp EventSetting 'AttrSet]
attrs
        EventSetting -> m EventSetting
forall (m :: * -> *) a. Monad m => a -> m a
return EventSetting
o


-- | A convenience alias for `Nothing` :: `Maybe` `EventSetting`.
noEventSetting :: Maybe EventSetting
noEventSetting :: Maybe EventSetting
noEventSetting = Maybe EventSetting
forall a. Maybe a
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' eventSetting #type
-- @
getEventSettingType :: MonadIO m => EventSetting -> m Gdk.Enums.EventType
getEventSettingType :: EventSetting -> m EventType
getEventSettingType s :: EventSetting
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
$ EventSetting -> (Ptr EventSetting -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
s ((Ptr EventSetting -> IO EventType) -> IO EventType)
-> (Ptr EventSetting -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventSetting
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventSetting
ptr Ptr EventSetting -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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' eventSetting [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventSettingType :: MonadIO m => EventSetting -> Gdk.Enums.EventType -> m ()
setEventSettingType :: EventSetting -> EventType -> m ()
setEventSettingType s :: EventSetting
s val :: 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
$ EventSetting -> (Ptr EventSetting -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
s ((Ptr EventSetting -> IO ()) -> IO ())
-> (Ptr EventSetting -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventSetting
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 EventSetting
ptr Ptr EventSetting -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CInt
val' :: CInt)

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

eventSetting_type :: AttrLabelProxy "type"
eventSetting_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' eventSetting #window
-- @
getEventSettingWindow :: MonadIO m => EventSetting -> m (Maybe Gdk.Window.Window)
getEventSettingWindow :: EventSetting -> m (Maybe Window)
getEventSettingWindow s :: EventSetting
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
$ EventSetting
-> (Ptr EventSetting -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
s ((Ptr EventSetting -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventSetting -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventSetting
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventSetting
ptr Ptr EventSetting -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ \val' :: 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' eventSetting [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventSettingWindow :: MonadIO m => EventSetting -> Ptr Gdk.Window.Window -> m ()
setEventSettingWindow :: EventSetting -> Ptr Window -> m ()
setEventSettingWindow s :: EventSetting
s val :: 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
$ EventSetting -> (Ptr EventSetting -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
s ((Ptr EventSetting -> IO ()) -> IO ())
-> (Ptr EventSetting -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventSetting
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventSetting
ptr Ptr EventSetting -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
-- @
clearEventSettingWindow :: MonadIO m => EventSetting -> m ()
clearEventSettingWindow :: EventSetting -> m ()
clearEventSettingWindow s :: EventSetting
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventSetting -> (Ptr EventSetting -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
s ((Ptr EventSetting -> IO ()) -> IO ())
-> (Ptr EventSetting -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventSetting
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventSetting
ptr Ptr EventSetting -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Window
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Window.Window)

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

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

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

eventSetting_sendEvent :: AttrLabelProxy "sendEvent"
eventSetting_sendEvent = AttrLabelProxy

#endif


-- | Get the value of the “@action@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventSetting #action
-- @
getEventSettingAction :: MonadIO m => EventSetting -> m Gdk.Enums.SettingAction
getEventSettingAction :: EventSetting -> m SettingAction
getEventSettingAction s :: EventSetting
s = IO SettingAction -> m SettingAction
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingAction -> m SettingAction)
-> IO SettingAction -> m SettingAction
forall a b. (a -> b) -> a -> b
$ EventSetting
-> (Ptr EventSetting -> IO SettingAction) -> IO SettingAction
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
s ((Ptr EventSetting -> IO SettingAction) -> IO SettingAction)
-> (Ptr EventSetting -> IO SettingAction) -> IO SettingAction
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventSetting
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventSetting
ptr Ptr EventSetting -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) :: IO CUInt
    let val' :: SettingAction
val' = (Int -> SettingAction
forall a. Enum a => Int -> a
toEnum (Int -> SettingAction) -> (CUInt -> Int) -> CUInt -> SettingAction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    SettingAction -> IO SettingAction
forall (m :: * -> *) a. Monad m => a -> m a
return SettingAction
val'

-- | Set the value of the “@action@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventSetting [ #action 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventSettingAction :: MonadIO m => EventSetting -> Gdk.Enums.SettingAction -> m ()
setEventSettingAction :: EventSetting -> SettingAction -> m ()
setEventSettingAction s :: EventSetting
s val :: SettingAction
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventSetting -> (Ptr EventSetting -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
s ((Ptr EventSetting -> IO ()) -> IO ())
-> (Ptr EventSetting -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventSetting
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (SettingAction -> Int) -> SettingAction -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SettingAction -> Int
forall a. Enum a => a -> Int
fromEnum) SettingAction
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventSetting
ptr Ptr EventSetting -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) (CUInt
val' :: CUInt)

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

eventSetting_action :: AttrLabelProxy "action"
eventSetting_action = AttrLabelProxy

#endif


-- | Get the value of the “@name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventSetting #name
-- @
getEventSettingName :: MonadIO m => EventSetting -> m (Maybe T.Text)
getEventSettingName :: EventSetting -> m (Maybe Text)
getEventSettingName s :: EventSetting
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ EventSetting
-> (Ptr EventSetting -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventSetting
s ((Ptr EventSetting -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr EventSetting -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventSetting
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventSetting
ptr Ptr EventSetting -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \val' :: CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

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

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

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

eventSetting_name :: AttrLabelProxy "name"
eventSetting_name = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
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)
type family ResolveEventSettingMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventSettingMethod l o = O.MethodResolutionFailed l o

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

#endif