{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Describes a change of keyboard focus.

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

module GI.Gdk.Structs.EventFocus
    ( 

-- * Exported types
    EventFocus(..)                          ,
    newZeroEventFocus                       ,
    noEventFocus                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveEventFocusMethod                 ,
#endif




 -- * Properties
-- ** in #attr:in#
-- | 'P.True' if the window has gained the keyboard focus, 'P.False' if
--   it has lost the focus.

#if defined(ENABLE_OVERLOADING)
    eventFocus_in                           ,
#endif
    getEventFocusIn                         ,
    setEventFocusIn                         ,


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

#if defined(ENABLE_OVERLOADING)
    eventFocus_sendEvent                    ,
#endif
    getEventFocusSendEvent                  ,
    setEventFocusSendEvent                  ,


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

#if defined(ENABLE_OVERLOADING)
    eventFocus_type                         ,
#endif
    getEventFocusType                       ,
    setEventFocusType                       ,


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

    clearEventFocusWindow                   ,
#if defined(ENABLE_OVERLOADING)
    eventFocus_window                       ,
#endif
    getEventFocusWindow                     ,
    setEventFocusWindow                     ,




    ) 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 EventFocus = EventFocus (ManagedPtr EventFocus)
    deriving (EventFocus -> EventFocus -> Bool
(EventFocus -> EventFocus -> Bool)
-> (EventFocus -> EventFocus -> Bool) -> Eq EventFocus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventFocus -> EventFocus -> Bool
$c/= :: EventFocus -> EventFocus -> Bool
== :: EventFocus -> EventFocus -> Bool
$c== :: EventFocus -> EventFocus -> Bool
Eq)
instance WrappedPtr EventFocus where
    wrappedPtrCalloc :: IO (Ptr EventFocus)
wrappedPtrCalloc = Int -> IO (Ptr EventFocus)
forall a. Int -> IO (Ptr a)
callocBytes 24
    wrappedPtrCopy :: EventFocus -> IO EventFocus
wrappedPtrCopy = \p :: EventFocus
p -> EventFocus -> (Ptr EventFocus -> IO EventFocus) -> IO EventFocus
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventFocus
p (Int -> Ptr EventFocus -> IO (Ptr EventFocus)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 24 (Ptr EventFocus -> IO (Ptr EventFocus))
-> (Ptr EventFocus -> IO EventFocus)
-> Ptr EventFocus
-> IO EventFocus
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventFocus -> EventFocus)
-> Ptr EventFocus -> IO EventFocus
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventFocus -> EventFocus
EventFocus)
    wrappedPtrFree :: Maybe (GDestroyNotify EventFocus)
wrappedPtrFree = GDestroyNotify EventFocus -> Maybe (GDestroyNotify EventFocus)
forall a. a -> Maybe a
Just GDestroyNotify EventFocus
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

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

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


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

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

eventFocus_type :: AttrLabelProxy "type"
eventFocus_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' eventFocus #window
-- @
getEventFocusWindow :: MonadIO m => EventFocus -> m (Maybe Gdk.Window.Window)
getEventFocusWindow :: EventFocus -> m (Maybe Window)
getEventFocusWindow s :: EventFocus
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
$ EventFocus
-> (Ptr EventFocus -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventFocus
s ((Ptr EventFocus -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventFocus -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventFocus
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventFocus
ptr Ptr EventFocus -> 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' eventFocus [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventFocusWindow :: MonadIO m => EventFocus -> Ptr Gdk.Window.Window -> m ()
setEventFocusWindow :: EventFocus -> Ptr Window -> m ()
setEventFocusWindow s :: EventFocus
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
$ EventFocus -> (Ptr EventFocus -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventFocus
s ((Ptr EventFocus -> IO ()) -> IO ())
-> (Ptr EventFocus -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventFocus
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventFocus
ptr Ptr EventFocus -> 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
-- @
clearEventFocusWindow :: MonadIO m => EventFocus -> m ()
clearEventFocusWindow :: EventFocus -> m ()
clearEventFocusWindow s :: EventFocus
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventFocus -> (Ptr EventFocus -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventFocus
s ((Ptr EventFocus -> IO ()) -> IO ())
-> (Ptr EventFocus -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventFocus
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventFocus
ptr Ptr EventFocus -> 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 EventFocusWindowFieldInfo
instance AttrInfo EventFocusWindowFieldInfo where
    type AttrBaseTypeConstraint EventFocusWindowFieldInfo = (~) EventFocus
    type AttrAllowedOps EventFocusWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventFocusWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventFocusWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventFocusWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventFocusWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventFocusWindowFieldInfo = "window"
    type AttrOrigin EventFocusWindowFieldInfo = EventFocus
    attrGet = getEventFocusWindow
    attrSet = setEventFocusWindow
    attrConstruct = undefined
    attrClear = clearEventFocusWindow
    attrTransfer _ v = do
        return v

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

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

eventFocus_sendEvent :: AttrLabelProxy "sendEvent"
eventFocus_sendEvent = AttrLabelProxy

#endif


-- | Get the value of the “@in@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventFocus #in
-- @
getEventFocusIn :: MonadIO m => EventFocus -> m Int16
getEventFocusIn :: EventFocus -> m Int16
getEventFocusIn s :: EventFocus
s = IO Int16 -> m Int16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int16 -> m Int16) -> IO Int16 -> m Int16
forall a b. (a -> b) -> a -> b
$ EventFocus -> (Ptr EventFocus -> IO Int16) -> IO Int16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventFocus
s ((Ptr EventFocus -> IO Int16) -> IO Int16)
-> (Ptr EventFocus -> IO Int16) -> IO Int16
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventFocus
ptr -> do
    Int16
val <- Ptr Int16 -> IO Int16
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventFocus
ptr Ptr EventFocus -> Int -> Ptr Int16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 18) :: IO Int16
    Int16 -> IO Int16
forall (m :: * -> *) a. Monad m => a -> m a
return Int16
val

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

#if defined(ENABLE_OVERLOADING)
data EventFocusInFieldInfo
instance AttrInfo EventFocusInFieldInfo where
    type AttrBaseTypeConstraint EventFocusInFieldInfo = (~) EventFocus
    type AttrAllowedOps EventFocusInFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventFocusInFieldInfo = (~) Int16
    type AttrTransferTypeConstraint EventFocusInFieldInfo = (~)Int16
    type AttrTransferType EventFocusInFieldInfo = Int16
    type AttrGetType EventFocusInFieldInfo = Int16
    type AttrLabel EventFocusInFieldInfo = "in"
    type AttrOrigin EventFocusInFieldInfo = EventFocus
    attrGet = getEventFocusIn
    attrSet = setEventFocusIn
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventFocus_in :: AttrLabelProxy "in"
eventFocus_in = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventFocus
type instance O.AttributeList EventFocus = EventFocusAttributeList
type EventFocusAttributeList = ('[ '("type", EventFocusTypeFieldInfo), '("window", EventFocusWindowFieldInfo), '("sendEvent", EventFocusSendEventFieldInfo), '("in", EventFocusInFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif