{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.EventButton
(
EventButton(..) ,
newZeroEventButton ,
#if defined(ENABLE_OVERLOADING)
ResolveEventButtonMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
eventButton_axes ,
#endif
getEventButtonAxes ,
setEventButtonAxes ,
#if defined(ENABLE_OVERLOADING)
eventButton_button ,
#endif
getEventButtonButton ,
setEventButtonButton ,
clearEventButtonDevice ,
#if defined(ENABLE_OVERLOADING)
eventButton_device ,
#endif
getEventButtonDevice ,
setEventButtonDevice ,
#if defined(ENABLE_OVERLOADING)
eventButton_sendEvent ,
#endif
getEventButtonSendEvent ,
setEventButtonSendEvent ,
#if defined(ENABLE_OVERLOADING)
eventButton_state ,
#endif
getEventButtonState ,
setEventButtonState ,
#if defined(ENABLE_OVERLOADING)
eventButton_time ,
#endif
getEventButtonTime ,
setEventButtonTime ,
#if defined(ENABLE_OVERLOADING)
eventButton_type ,
#endif
getEventButtonType ,
setEventButtonType ,
clearEventButtonWindow ,
#if defined(ENABLE_OVERLOADING)
eventButton_window ,
#endif
getEventButtonWindow ,
setEventButtonWindow ,
#if defined(ENABLE_OVERLOADING)
eventButton_x ,
#endif
getEventButtonX ,
setEventButtonX ,
#if defined(ENABLE_OVERLOADING)
eventButton_xRoot ,
#endif
getEventButtonXRoot ,
setEventButtonXRoot ,
#if defined(ENABLE_OVERLOADING)
eventButton_y ,
#endif
getEventButtonY ,
setEventButtonY ,
#if defined(ENABLE_OVERLOADING)
eventButton_yRoot ,
#endif
getEventButtonYRoot ,
setEventButtonYRoot ,
) 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.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.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 {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
newtype EventButton = EventButton (SP.ManagedPtr EventButton)
deriving (EventButton -> EventButton -> Bool
(EventButton -> EventButton -> Bool)
-> (EventButton -> EventButton -> Bool) -> Eq EventButton
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventButton -> EventButton -> Bool
$c/= :: EventButton -> EventButton -> Bool
== :: EventButton -> EventButton -> Bool
$c== :: EventButton -> EventButton -> Bool
Eq)
instance SP.ManagedPtrNewtype EventButton where
toManagedPtr :: EventButton -> ManagedPtr EventButton
toManagedPtr (EventButton ManagedPtr EventButton
p) = ManagedPtr EventButton
p
instance BoxedPtr EventButton where
boxedPtrCopy :: EventButton -> IO EventButton
boxedPtrCopy = \EventButton
p -> EventButton
-> (Ptr EventButton -> IO EventButton) -> IO EventButton
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EventButton
p (Int -> Ptr EventButton -> IO (Ptr EventButton)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
80 (Ptr EventButton -> IO (Ptr EventButton))
-> (Ptr EventButton -> IO EventButton)
-> Ptr EventButton
-> IO EventButton
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventButton -> EventButton)
-> Ptr EventButton -> IO EventButton
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr EventButton -> EventButton
EventButton)
boxedPtrFree :: EventButton -> IO ()
boxedPtrFree = \EventButton
x -> EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr EventButton
x Ptr EventButton -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr EventButton where
boxedPtrCalloc :: IO (Ptr EventButton)
boxedPtrCalloc = Int -> IO (Ptr EventButton)
forall a. Int -> IO (Ptr a)
callocBytes Int
80
newZeroEventButton :: MonadIO m => m EventButton
newZeroEventButton :: forall (m :: * -> *). MonadIO m => m EventButton
newZeroEventButton = IO EventButton -> m EventButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventButton -> m EventButton)
-> IO EventButton -> m EventButton
forall a b. (a -> b) -> a -> b
$ IO (Ptr EventButton)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr EventButton)
-> (Ptr EventButton -> IO EventButton) -> IO EventButton
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventButton -> EventButton)
-> Ptr EventButton -> IO EventButton
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventButton -> EventButton
EventButton
instance tag ~ 'AttrSet => Constructible EventButton tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr EventButton -> EventButton)
-> [AttrOp EventButton tag] -> m EventButton
new ManagedPtr EventButton -> EventButton
_ [AttrOp EventButton tag]
attrs = do
EventButton
o <- m EventButton
forall (m :: * -> *). MonadIO m => m EventButton
newZeroEventButton
EventButton -> [AttrOp EventButton 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set EventButton
o [AttrOp EventButton tag]
[AttrOp EventButton 'AttrSet]
attrs
EventButton -> m EventButton
forall (m :: * -> *) a. Monad m => a -> m a
return EventButton
o
getEventButtonType :: MonadIO m => EventButton -> m Gdk.Enums.EventType
getEventButtonType :: forall (m :: * -> *). MonadIO m => EventButton -> m EventType
getEventButtonType EventButton
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
$ EventButton -> (Ptr EventButton -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO EventType) -> IO EventType)
-> (Ptr EventButton -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> 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 (m :: * -> *) a. Monad m => a -> m a
return EventType
val'
setEventButtonType :: MonadIO m => EventButton -> Gdk.Enums.EventType -> m ()
setEventButtonType :: forall (m :: * -> *). MonadIO m => EventButton -> EventType -> m ()
setEventButtonType EventButton
s 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
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
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 EventButton
ptr Ptr EventButton -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CInt
val' :: CInt)
#if defined(ENABLE_OVERLOADING)
data EventButtonTypeFieldInfo
instance AttrInfo EventButtonTypeFieldInfo where
type AttrBaseTypeConstraint EventButtonTypeFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrTransferTypeConstraint EventButtonTypeFieldInfo = (~)Gdk.Enums.EventType
type AttrTransferType EventButtonTypeFieldInfo = Gdk.Enums.EventType
type AttrGetType EventButtonTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventButtonTypeFieldInfo = "type"
type AttrOrigin EventButtonTypeFieldInfo = EventButton
attrGet = getEventButtonType
attrSet = setEventButtonType
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.type"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:type"
})
eventButton_type :: AttrLabelProxy "type"
eventButton_type = AttrLabelProxy
#endif
getEventButtonWindow :: MonadIO m => EventButton -> m (Maybe Gdk.Window.Window)
getEventButtonWindow :: forall (m :: * -> *). MonadIO m => EventButton -> m (Maybe Window)
getEventButtonWindow EventButton
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
$ EventButton
-> (Ptr EventButton -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventButton -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> 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 (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
setEventButtonWindow :: MonadIO m => EventButton -> Ptr Gdk.Window.Window -> m ()
setEventButtonWindow :: forall (m :: * -> *).
MonadIO m =>
EventButton -> Ptr Window -> m ()
setEventButtonWindow EventButton
s 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
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr Window
val :: Ptr Gdk.Window.Window)
clearEventButtonWindow :: MonadIO m => EventButton -> m ()
clearEventButtonWindow :: forall (m :: * -> *). MonadIO m => EventButton -> m ()
clearEventButtonWindow EventButton
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> 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 EventButtonWindowFieldInfo
instance AttrInfo EventButtonWindowFieldInfo where
type AttrBaseTypeConstraint EventButtonWindowFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventButtonWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrTransferTypeConstraint EventButtonWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
type AttrTransferType EventButtonWindowFieldInfo = (Ptr Gdk.Window.Window)
type AttrGetType EventButtonWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventButtonWindowFieldInfo = "window"
type AttrOrigin EventButtonWindowFieldInfo = EventButton
attrGet = getEventButtonWindow
attrSet = setEventButtonWindow
attrConstruct = undefined
attrClear = clearEventButtonWindow
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.window"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:window"
})
eventButton_window :: AttrLabelProxy "window"
eventButton_window = AttrLabelProxy
#endif
getEventButtonSendEvent :: MonadIO m => EventButton -> m Int8
getEventButtonSendEvent :: forall (m :: * -> *). MonadIO m => EventButton -> m Int8
getEventButtonSendEvent EventButton
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
$ EventButton -> (Ptr EventButton -> IO Int8) -> IO Int8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Int8) -> IO Int8)
-> (Ptr EventButton -> IO Int8) -> IO Int8
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Int8
val <- Ptr Int8 -> IO Int8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int8
Int8 -> IO Int8
forall (m :: * -> *) a. Monad m => a -> m a
return Int8
val
setEventButtonSendEvent :: MonadIO m => EventButton -> Int8 -> m ()
setEventButtonSendEvent :: forall (m :: * -> *). MonadIO m => EventButton -> Int8 -> m ()
setEventButtonSendEvent EventButton
s 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
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr Int8 -> Int8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int8
val :: Int8)
#if defined(ENABLE_OVERLOADING)
data EventButtonSendEventFieldInfo
instance AttrInfo EventButtonSendEventFieldInfo where
type AttrBaseTypeConstraint EventButtonSendEventFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonSendEventFieldInfo = (~) Int8
type AttrTransferTypeConstraint EventButtonSendEventFieldInfo = (~)Int8
type AttrTransferType EventButtonSendEventFieldInfo = Int8
type AttrGetType EventButtonSendEventFieldInfo = Int8
type AttrLabel EventButtonSendEventFieldInfo = "send_event"
type AttrOrigin EventButtonSendEventFieldInfo = EventButton
attrGet = getEventButtonSendEvent
attrSet = setEventButtonSendEvent
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.sendEvent"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:sendEvent"
})
eventButton_sendEvent :: AttrLabelProxy "sendEvent"
eventButton_sendEvent = AttrLabelProxy
#endif
getEventButtonTime :: MonadIO m => EventButton -> m Word32
getEventButtonTime :: forall (m :: * -> *). MonadIO m => EventButton -> m Word32
getEventButtonTime EventButton
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Word32) -> IO Word32)
-> (Ptr EventButton -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setEventButtonTime :: MonadIO m => EventButton -> Word32 -> m ()
setEventButtonTime :: forall (m :: * -> *). MonadIO m => EventButton -> Word32 -> m ()
setEventButtonTime EventButton
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data EventButtonTimeFieldInfo
instance AttrInfo EventButtonTimeFieldInfo where
type AttrBaseTypeConstraint EventButtonTimeFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonTimeFieldInfo = (~) Word32
type AttrTransferTypeConstraint EventButtonTimeFieldInfo = (~)Word32
type AttrTransferType EventButtonTimeFieldInfo = Word32
type AttrGetType EventButtonTimeFieldInfo = Word32
type AttrLabel EventButtonTimeFieldInfo = "time"
type AttrOrigin EventButtonTimeFieldInfo = EventButton
attrGet = getEventButtonTime
attrSet = setEventButtonTime
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.time"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:time"
})
eventButton_time :: AttrLabelProxy "time"
eventButton_time = AttrLabelProxy
#endif
getEventButtonX :: MonadIO m => EventButton -> m Double
getEventButtonX :: forall (m :: * -> *). MonadIO m => EventButton -> m Double
getEventButtonX EventButton
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setEventButtonX :: MonadIO m => EventButton -> Double -> m ()
setEventButtonX :: forall (m :: * -> *). MonadIO m => EventButton -> Double -> m ()
setEventButtonX EventButton
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data EventButtonXFieldInfo
instance AttrInfo EventButtonXFieldInfo where
type AttrBaseTypeConstraint EventButtonXFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonXFieldInfo = (~) Double
type AttrTransferTypeConstraint EventButtonXFieldInfo = (~)Double
type AttrTransferType EventButtonXFieldInfo = Double
type AttrGetType EventButtonXFieldInfo = Double
type AttrLabel EventButtonXFieldInfo = "x"
type AttrOrigin EventButtonXFieldInfo = EventButton
attrGet = getEventButtonX
attrSet = setEventButtonX
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.x"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:x"
})
eventButton_x :: AttrLabelProxy "x"
eventButton_x = AttrLabelProxy
#endif
getEventButtonY :: MonadIO m => EventButton -> m Double
getEventButtonY :: forall (m :: * -> *). MonadIO m => EventButton -> m Double
getEventButtonY EventButton
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setEventButtonY :: MonadIO m => EventButton -> Double -> m ()
setEventButtonY :: forall (m :: * -> *). MonadIO m => EventButton -> Double -> m ()
setEventButtonY EventButton
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data EventButtonYFieldInfo
instance AttrInfo EventButtonYFieldInfo where
type AttrBaseTypeConstraint EventButtonYFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonYFieldInfo = (~) Double
type AttrTransferTypeConstraint EventButtonYFieldInfo = (~)Double
type AttrTransferType EventButtonYFieldInfo = Double
type AttrGetType EventButtonYFieldInfo = Double
type AttrLabel EventButtonYFieldInfo = "y"
type AttrOrigin EventButtonYFieldInfo = EventButton
attrGet = getEventButtonY
attrSet = setEventButtonY
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.y"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:y"
})
eventButton_y :: AttrLabelProxy "y"
eventButton_y = AttrLabelProxy
#endif
getEventButtonAxes :: MonadIO m => EventButton -> m Double
getEventButtonAxes :: forall (m :: * -> *). MonadIO m => EventButton -> m Double
getEventButtonAxes EventButton
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setEventButtonAxes :: MonadIO m => EventButton -> Double -> m ()
setEventButtonAxes :: forall (m :: * -> *). MonadIO m => EventButton -> Double -> m ()
setEventButtonAxes EventButton
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data EventButtonAxesFieldInfo
instance AttrInfo EventButtonAxesFieldInfo where
type AttrBaseTypeConstraint EventButtonAxesFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonAxesFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonAxesFieldInfo = (~) Double
type AttrTransferTypeConstraint EventButtonAxesFieldInfo = (~)Double
type AttrTransferType EventButtonAxesFieldInfo = Double
type AttrGetType EventButtonAxesFieldInfo = Double
type AttrLabel EventButtonAxesFieldInfo = "axes"
type AttrOrigin EventButtonAxesFieldInfo = EventButton
attrGet = getEventButtonAxes
attrSet = setEventButtonAxes
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.axes"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:axes"
})
eventButton_axes :: AttrLabelProxy "axes"
eventButton_axes = AttrLabelProxy
#endif
getEventButtonState :: MonadIO m => EventButton -> m [Gdk.Flags.ModifierType]
getEventButtonState :: forall (m :: * -> *). MonadIO m => EventButton -> m [ModifierType]
getEventButtonState EventButton
s = IO [ModifierType] -> m [ModifierType]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ModifierType] -> m [ModifierType])
-> IO [ModifierType] -> m [ModifierType]
forall a b. (a -> b) -> a -> b
$ EventButton
-> (Ptr EventButton -> IO [ModifierType]) -> IO [ModifierType]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO [ModifierType]) -> IO [ModifierType])
-> (Ptr EventButton -> IO [ModifierType]) -> IO [ModifierType]
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) :: IO CUInt
let val' :: [ModifierType]
val' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
[ModifierType] -> IO [ModifierType]
forall (m :: * -> *) a. Monad m => a -> m a
return [ModifierType]
val'
setEventButtonState :: MonadIO m => EventButton -> [Gdk.Flags.ModifierType] -> m ()
setEventButtonState :: forall (m :: * -> *).
MonadIO m =>
EventButton -> [ModifierType] -> m ()
setEventButtonState EventButton
s [ModifierType]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
let val' :: CUInt
val' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data EventButtonStateFieldInfo
instance AttrInfo EventButtonStateFieldInfo where
type AttrBaseTypeConstraint EventButtonStateFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonStateFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonStateFieldInfo = (~) [Gdk.Flags.ModifierType]
type AttrTransferTypeConstraint EventButtonStateFieldInfo = (~)[Gdk.Flags.ModifierType]
type AttrTransferType EventButtonStateFieldInfo = [Gdk.Flags.ModifierType]
type AttrGetType EventButtonStateFieldInfo = [Gdk.Flags.ModifierType]
type AttrLabel EventButtonStateFieldInfo = "state"
type AttrOrigin EventButtonStateFieldInfo = EventButton
attrGet = getEventButtonState
attrSet = setEventButtonState
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.state"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:state"
})
eventButton_state :: AttrLabelProxy "state"
eventButton_state = AttrLabelProxy
#endif
getEventButtonButton :: MonadIO m => EventButton -> m Word32
getEventButtonButton :: forall (m :: * -> *). MonadIO m => EventButton -> m Word32
getEventButtonButton EventButton
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Word32) -> IO Word32)
-> (Ptr EventButton -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setEventButtonButton :: MonadIO m => EventButton -> Word32 -> m ()
setEventButtonButton :: forall (m :: * -> *). MonadIO m => EventButton -> Word32 -> m ()
setEventButtonButton EventButton
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data EventButtonButtonFieldInfo
instance AttrInfo EventButtonButtonFieldInfo where
type AttrBaseTypeConstraint EventButtonButtonFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonButtonFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonButtonFieldInfo = (~) Word32
type AttrTransferTypeConstraint EventButtonButtonFieldInfo = (~)Word32
type AttrTransferType EventButtonButtonFieldInfo = Word32
type AttrGetType EventButtonButtonFieldInfo = Word32
type AttrLabel EventButtonButtonFieldInfo = "button"
type AttrOrigin EventButtonButtonFieldInfo = EventButton
attrGet = getEventButtonButton
attrSet = setEventButtonButton
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.button"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:button"
})
eventButton_button :: AttrLabelProxy "button"
eventButton_button = AttrLabelProxy
#endif
getEventButtonDevice :: MonadIO m => EventButton -> m (Maybe Gdk.Device.Device)
getEventButtonDevice :: forall (m :: * -> *). MonadIO m => EventButton -> m (Maybe Device)
getEventButtonDevice EventButton
s = IO (Maybe Device) -> m (Maybe Device)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Device) -> m (Maybe Device))
-> IO (Maybe Device) -> m (Maybe Device)
forall a b. (a -> b) -> a -> b
$ EventButton
-> (Ptr EventButton -> IO (Maybe Device)) -> IO (Maybe Device)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO (Maybe Device)) -> IO (Maybe Device))
-> (Ptr EventButton -> IO (Maybe Device)) -> IO (Maybe Device)
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr Device
val <- Ptr (Ptr Device) -> IO (Ptr Device)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) :: IO (Ptr Gdk.Device.Device)
Maybe Device
result <- Ptr Device -> (Ptr Device -> IO Device) -> IO (Maybe Device)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Device
val ((Ptr Device -> IO Device) -> IO (Maybe Device))
-> (Ptr Device -> IO Device) -> IO (Maybe Device)
forall a b. (a -> b) -> a -> b
$ \Ptr Device
val' -> do
Device
val'' <- ((ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Device -> Device
Gdk.Device.Device) Ptr Device
val'
Device -> IO Device
forall (m :: * -> *) a. Monad m => a -> m a
return Device
val''
Maybe Device -> IO (Maybe Device)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Device
result
setEventButtonDevice :: MonadIO m => EventButton -> Ptr Gdk.Device.Device -> m ()
setEventButtonDevice :: forall (m :: * -> *).
MonadIO m =>
EventButton -> Ptr Device -> m ()
setEventButtonDevice EventButton
s Ptr Device
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr (Ptr Device) -> Ptr Device -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (Ptr Device
val :: Ptr Gdk.Device.Device)
clearEventButtonDevice :: MonadIO m => EventButton -> m ()
clearEventButtonDevice :: forall (m :: * -> *). MonadIO m => EventButton -> m ()
clearEventButtonDevice EventButton
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
Ptr (Ptr Device) -> Ptr Device -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (Ptr Device
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Device.Device)
#if defined(ENABLE_OVERLOADING)
data EventButtonDeviceFieldInfo
instance AttrInfo EventButtonDeviceFieldInfo where
type AttrBaseTypeConstraint EventButtonDeviceFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonDeviceFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventButtonDeviceFieldInfo = (~) (Ptr Gdk.Device.Device)
type AttrTransferTypeConstraint EventButtonDeviceFieldInfo = (~)(Ptr Gdk.Device.Device)
type AttrTransferType EventButtonDeviceFieldInfo = (Ptr Gdk.Device.Device)
type AttrGetType EventButtonDeviceFieldInfo = Maybe Gdk.Device.Device
type AttrLabel EventButtonDeviceFieldInfo = "device"
type AttrOrigin EventButtonDeviceFieldInfo = EventButton
attrGet = getEventButtonDevice
attrSet = setEventButtonDevice
attrConstruct = undefined
attrClear = clearEventButtonDevice
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.device"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:device"
})
eventButton_device :: AttrLabelProxy "device"
eventButton_device = AttrLabelProxy
#endif
getEventButtonXRoot :: MonadIO m => EventButton -> m Double
getEventButtonXRoot :: forall (m :: * -> *). MonadIO m => EventButton -> m Double
getEventButtonXRoot EventButton
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setEventButtonXRoot :: MonadIO m => EventButton -> Double -> m ()
setEventButtonXRoot :: forall (m :: * -> *). MonadIO m => EventButton -> Double -> m ()
setEventButtonXRoot EventButton
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data EventButtonXRootFieldInfo
instance AttrInfo EventButtonXRootFieldInfo where
type AttrBaseTypeConstraint EventButtonXRootFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonXRootFieldInfo = (~) Double
type AttrTransferTypeConstraint EventButtonXRootFieldInfo = (~)Double
type AttrTransferType EventButtonXRootFieldInfo = Double
type AttrGetType EventButtonXRootFieldInfo = Double
type AttrLabel EventButtonXRootFieldInfo = "x_root"
type AttrOrigin EventButtonXRootFieldInfo = EventButton
attrGet = getEventButtonXRoot
attrSet = setEventButtonXRoot
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.xRoot"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:xRoot"
})
eventButton_xRoot :: AttrLabelProxy "xRoot"
eventButton_xRoot = AttrLabelProxy
#endif
getEventButtonYRoot :: MonadIO m => EventButton -> m Double
getEventButtonYRoot :: forall (m :: * -> *). MonadIO m => EventButton -> m Double
getEventButtonYRoot EventButton
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) :: IO CDouble
let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setEventButtonYRoot :: MonadIO m => EventButton -> Double -> m ()
setEventButtonYRoot :: forall (m :: * -> *). MonadIO m => EventButton -> Double -> m ()
setEventButtonYRoot EventButton
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventButton
ptr -> do
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data EventButtonYRootFieldInfo
instance AttrInfo EventButtonYRootFieldInfo where
type AttrBaseTypeConstraint EventButtonYRootFieldInfo = (~) EventButton
type AttrAllowedOps EventButtonYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonYRootFieldInfo = (~) Double
type AttrTransferTypeConstraint EventButtonYRootFieldInfo = (~)Double
type AttrTransferType EventButtonYRootFieldInfo = Double
type AttrGetType EventButtonYRootFieldInfo = Double
type AttrLabel EventButtonYRootFieldInfo = "y_root"
type AttrOrigin EventButtonYRootFieldInfo = EventButton
attrGet = getEventButtonYRoot
attrSet = setEventButtonYRoot
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventButton.yRoot"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Structs-EventButton.html#g:attr:yRoot"
})
eventButton_yRoot :: AttrLabelProxy "yRoot"
eventButton_yRoot = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventButton
type instance O.AttributeList EventButton = EventButtonAttributeList
type EventButtonAttributeList = ('[ '("type", EventButtonTypeFieldInfo), '("window", EventButtonWindowFieldInfo), '("sendEvent", EventButtonSendEventFieldInfo), '("time", EventButtonTimeFieldInfo), '("x", EventButtonXFieldInfo), '("y", EventButtonYFieldInfo), '("axes", EventButtonAxesFieldInfo), '("state", EventButtonStateFieldInfo), '("button", EventButtonButtonFieldInfo), '("device", EventButtonDeviceFieldInfo), '("xRoot", EventButtonXRootFieldInfo), '("yRoot", EventButtonYRootFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveEventButtonMethod (t :: Symbol) (o :: *) :: * where
ResolveEventButtonMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventButtonMethod t EventButton, O.OverloadedMethod info EventButton p) => OL.IsLabel t (EventButton -> 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 ~ ResolveEventButtonMethod t EventButton, O.OverloadedMethod info EventButton p, R.HasField t EventButton p) => R.HasField t EventButton p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveEventButtonMethod t EventButton, O.OverloadedMethodInfo info EventButton) => OL.IsLabel t (O.MethodProxy info EventButton) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif