{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.EventFocus
(
EventFocus(..) ,
newZeroEventFocus ,
#if defined(ENABLE_OVERLOADING)
ResolveEventFocusMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
eventFocus_in ,
#endif
getEventFocusIn ,
setEventFocusIn ,
#if defined(ENABLE_OVERLOADING)
eventFocus_sendEvent ,
#endif
getEventFocusSendEvent ,
setEventFocusSendEvent ,
#if defined(ENABLE_OVERLOADING)
eventFocus_type ,
#endif
getEventFocusType ,
setEventFocusType ,
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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Pattern as Cairo.Pattern
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Callbacks as Gdk.Callbacks
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceManager as Gdk.DeviceManager
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.DragContext as Gdk.DragContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawingContext as Gdk.DrawingContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import {-# SOURCE #-} qualified GI.Gdk.Objects.GLContext as Gdk.GLContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Screen as Gdk.Screen
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Visual as Gdk.Visual
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
import {-# SOURCE #-} qualified GI.Gdk.Structs.Color as Gdk.Color
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventDND as Gdk.EventDND
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadAxis as Gdk.EventPadAxis
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadButton as Gdk.EventPadButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadGroupMode as Gdk.EventPadGroupMode
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSetting as Gdk.EventSetting
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouch as Gdk.EventTouch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadPinch as Gdk.EventTouchpadPinch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadSwipe as Gdk.EventTouchpadSwipe
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import {-# SOURCE #-} qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.WindowAttr as Gdk.WindowAttr
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext
#else
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
#endif
newtype EventFocus = EventFocus (SP.ManagedPtr EventFocus)
deriving (EventFocus -> EventFocus -> Bool
(EventFocus -> EventFocus -> Bool)
-> (EventFocus -> EventFocus -> Bool) -> Eq EventFocus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventFocus -> EventFocus -> Bool
== :: EventFocus -> EventFocus -> Bool
$c/= :: EventFocus -> EventFocus -> Bool
/= :: EventFocus -> EventFocus -> Bool
Eq)
instance SP.ManagedPtrNewtype EventFocus where
toManagedPtr :: EventFocus -> ManagedPtr EventFocus
toManagedPtr (EventFocus ManagedPtr EventFocus
p) = ManagedPtr EventFocus
p
instance BoxedPtr EventFocus where
boxedPtrCopy :: EventFocus -> IO EventFocus
boxedPtrCopy = \EventFocus
p -> EventFocus -> (Ptr EventFocus -> IO EventFocus) -> IO EventFocus
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EventFocus
p (Int -> Ptr EventFocus -> IO (Ptr EventFocus)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
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, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr EventFocus -> EventFocus
EventFocus)
boxedPtrFree :: EventFocus -> IO ()
boxedPtrFree = \EventFocus
x -> EventFocus -> (Ptr EventFocus -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr EventFocus
x Ptr EventFocus -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr EventFocus where
boxedPtrCalloc :: IO (Ptr EventFocus)
boxedPtrCalloc = Int -> IO (Ptr EventFocus)
forall a. Int -> IO (Ptr a)
callocBytes Int
24
newZeroEventFocus :: MonadIO m => m EventFocus
newZeroEventFocus :: forall (m :: * -> *). MonadIO m => m EventFocus
newZeroEventFocus = IO EventFocus -> m EventFocus
forall a. IO a -> m a
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. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr EventFocus)
-> (Ptr EventFocus -> IO EventFocus) -> IO EventFocus
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventFocus -> EventFocus)
-> Ptr EventFocus -> IO EventFocus
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventFocus -> EventFocus
EventFocus
instance tag ~ 'AttrSet => Constructible EventFocus tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr EventFocus -> EventFocus)
-> [AttrOp EventFocus tag] -> m EventFocus
new ManagedPtr EventFocus -> EventFocus
_ [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 a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return EventFocus
o
getEventFocusType :: MonadIO m => EventFocus -> m Gdk.Enums.EventType
getEventFocusType :: forall (m :: * -> *). MonadIO m => EventFocus -> m EventType
getEventFocusType EventFocus
s = IO EventType -> m EventType
forall a. IO a -> m a
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 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` Int
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EventType
val'
setEventFocusType :: MonadIO m => EventFocus -> Gdk.Enums.EventType -> m ()
setEventFocusType :: forall (m :: * -> *). MonadIO m => EventFocus -> EventType -> m ()
setEventFocusType EventFocus
s EventType
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventFocus.type"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventFocus.html#g:attr:type"
})
eventFocus_type :: AttrLabelProxy "type"
eventFocus_type = AttrLabelProxy
#endif
getEventFocusWindow :: MonadIO m => EventFocus -> m (Maybe Gdk.Window.Window)
getEventFocusWindow :: forall (m :: * -> *). MonadIO m => EventFocus -> m (Maybe Window)
getEventFocusWindow EventFocus
s = IO (Maybe Window) -> m (Maybe Window)
forall a. IO a -> m a
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 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` Int
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
$ \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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Window
val''
Maybe Window -> IO (Maybe Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
result
setEventFocusWindow :: MonadIO m => EventFocus -> Ptr Gdk.Window.Window -> m ()
setEventFocusWindow :: forall (m :: * -> *). MonadIO m => EventFocus -> Ptr Window -> m ()
setEventFocusWindow EventFocus
s Ptr Window
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
8) (Ptr Window
val :: Ptr Gdk.Window.Window)
clearEventFocusWindow :: MonadIO m => EventFocus -> m ()
clearEventFocusWindow :: forall (m :: * -> *). MonadIO m => EventFocus -> m ()
clearEventFocusWindow EventFocus
s = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventFocus.window"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventFocus.html#g:attr:window"
})
eventFocus_window :: AttrLabelProxy "window"
eventFocus_window = AttrLabelProxy
#endif
getEventFocusSendEvent :: MonadIO m => EventFocus -> m Int8
getEventFocusSendEvent :: forall (m :: * -> *). MonadIO m => EventFocus -> m Int8
getEventFocusSendEvent EventFocus
s = IO Int8 -> m Int8
forall a. IO a -> m a
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 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` Int
16) :: IO Int8
Int8 -> IO Int8
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int8
val
setEventFocusSendEvent :: MonadIO m => EventFocus -> Int8 -> m ()
setEventFocusSendEvent :: forall (m :: * -> *). MonadIO m => EventFocus -> Int8 -> m ()
setEventFocusSendEvent EventFocus
s Int8
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventFocus.sendEvent"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventFocus.html#g:attr:sendEvent"
})
eventFocus_sendEvent :: AttrLabelProxy "sendEvent"
eventFocus_sendEvent = AttrLabelProxy
#endif
getEventFocusIn :: MonadIO m => EventFocus -> m Int16
getEventFocusIn :: forall (m :: * -> *). MonadIO m => EventFocus -> m Int16
getEventFocusIn EventFocus
s = IO Int16 -> m Int16
forall a. IO a -> m a
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 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` Int
18) :: IO Int16
Int16 -> IO Int16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int16
val
setEventFocusIn :: MonadIO m => EventFocus -> Int16 -> m ()
setEventFocusIn :: forall (m :: * -> *). MonadIO m => EventFocus -> Int16 -> m ()
setEventFocusIn EventFocus
s Int16
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventFocus.in"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventFocus.html#g:attr:in"
})
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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveEventFocusMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveEventFocusMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventFocusMethod t EventFocus, O.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveEventFocusMethod t EventFocus, O.OverloadedMethod info EventFocus p, R.HasField t EventFocus p) => R.HasField t EventFocus p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveEventFocusMethod t EventFocus, O.OverloadedMethodInfo info EventFocus) => OL.IsLabel t (O.MethodProxy info EventFocus) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif