#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gdk.Structs.EventProximity
(
EventProximity(..) ,
newZeroEventProximity ,
noEventProximity ,
clearEventProximityDevice ,
#if ENABLE_OVERLOADING
eventProximity_device ,
#endif
getEventProximityDevice ,
setEventProximityDevice ,
#if ENABLE_OVERLOADING
eventProximity_sendEvent ,
#endif
getEventProximitySendEvent ,
setEventProximitySendEvent ,
#if ENABLE_OVERLOADING
eventProximity_time ,
#endif
getEventProximityTime ,
setEventProximityTime ,
#if ENABLE_OVERLOADING
eventProximity_type ,
#endif
getEventProximityType ,
setEventProximityType ,
clearEventProximityWindow ,
#if ENABLE_OVERLOADING
eventProximity_window ,
#endif
getEventProximityWindow ,
setEventProximityWindow ,
) 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.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.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
newtype EventProximity = EventProximity (ManagedPtr EventProximity)
instance WrappedPtr EventProximity where
wrappedPtrCalloc = callocBytes 32
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 32 >=> wrapPtr EventProximity)
wrappedPtrFree = Just ptr_to_g_free
newZeroEventProximity :: MonadIO m => m EventProximity
newZeroEventProximity = liftIO $ wrappedPtrCalloc >>= wrapPtr EventProximity
instance tag ~ 'AttrSet => Constructible EventProximity tag where
new _ attrs = do
o <- newZeroEventProximity
GI.Attributes.set o attrs
return o
noEventProximity :: Maybe EventProximity
noEventProximity = Nothing
getEventProximityType :: MonadIO m => EventProximity -> m Gdk.Enums.EventType
getEventProximityType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CInt
let val' = (toEnum . fromIntegral) val
return val'
setEventProximityType :: MonadIO m => EventProximity -> Gdk.Enums.EventType -> m ()
setEventProximityType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 0) (val' :: CInt)
#if ENABLE_OVERLOADING
data EventProximityTypeFieldInfo
instance AttrInfo EventProximityTypeFieldInfo where
type AttrAllowedOps EventProximityTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventProximityTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrBaseTypeConstraint EventProximityTypeFieldInfo = (~) EventProximity
type AttrGetType EventProximityTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventProximityTypeFieldInfo = "type"
type AttrOrigin EventProximityTypeFieldInfo = EventProximity
attrGet _ = getEventProximityType
attrSet _ = setEventProximityType
attrConstruct = undefined
attrClear _ = undefined
eventProximity_type :: AttrLabelProxy "type"
eventProximity_type = AttrLabelProxy
#endif
getEventProximityWindow :: MonadIO m => EventProximity -> m (Maybe Gdk.Window.Window)
getEventProximityWindow s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO (Ptr Gdk.Window.Window)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.Window.Window) val'
return val''
return result
setEventProximityWindow :: MonadIO m => EventProximity -> Ptr Gdk.Window.Window -> m ()
setEventProximityWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventProximityWindow :: MonadIO m => EventProximity -> m ()
clearEventProximityWindow s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
#if ENABLE_OVERLOADING
data EventProximityWindowFieldInfo
instance AttrInfo EventProximityWindowFieldInfo where
type AttrAllowedOps EventProximityWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventProximityWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrBaseTypeConstraint EventProximityWindowFieldInfo = (~) EventProximity
type AttrGetType EventProximityWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventProximityWindowFieldInfo = "window"
type AttrOrigin EventProximityWindowFieldInfo = EventProximity
attrGet _ = getEventProximityWindow
attrSet _ = setEventProximityWindow
attrConstruct = undefined
attrClear _ = clearEventProximityWindow
eventProximity_window :: AttrLabelProxy "window"
eventProximity_window = AttrLabelProxy
#endif
getEventProximitySendEvent :: MonadIO m => EventProximity -> m Int8
getEventProximitySendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int8
return val
setEventProximitySendEvent :: MonadIO m => EventProximity -> Int8 -> m ()
setEventProximitySendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int8)
#if ENABLE_OVERLOADING
data EventProximitySendEventFieldInfo
instance AttrInfo EventProximitySendEventFieldInfo where
type AttrAllowedOps EventProximitySendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventProximitySendEventFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventProximitySendEventFieldInfo = (~) EventProximity
type AttrGetType EventProximitySendEventFieldInfo = Int8
type AttrLabel EventProximitySendEventFieldInfo = "send_event"
type AttrOrigin EventProximitySendEventFieldInfo = EventProximity
attrGet _ = getEventProximitySendEvent
attrSet _ = setEventProximitySendEvent
attrConstruct = undefined
attrClear _ = undefined
eventProximity_sendEvent :: AttrLabelProxy "sendEvent"
eventProximity_sendEvent = AttrLabelProxy
#endif
getEventProximityTime :: MonadIO m => EventProximity -> m Word32
getEventProximityTime s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 20) :: IO Word32
return val
setEventProximityTime :: MonadIO m => EventProximity -> Word32 -> m ()
setEventProximityTime s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 20) (val :: Word32)
#if ENABLE_OVERLOADING
data EventProximityTimeFieldInfo
instance AttrInfo EventProximityTimeFieldInfo where
type AttrAllowedOps EventProximityTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventProximityTimeFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventProximityTimeFieldInfo = (~) EventProximity
type AttrGetType EventProximityTimeFieldInfo = Word32
type AttrLabel EventProximityTimeFieldInfo = "time"
type AttrOrigin EventProximityTimeFieldInfo = EventProximity
attrGet _ = getEventProximityTime
attrSet _ = setEventProximityTime
attrConstruct = undefined
attrClear _ = undefined
eventProximity_time :: AttrLabelProxy "time"
eventProximity_time = AttrLabelProxy
#endif
getEventProximityDevice :: MonadIO m => EventProximity -> m (Maybe Gdk.Device.Device)
getEventProximityDevice s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO (Ptr Gdk.Device.Device)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.Device.Device) val'
return val''
return result
setEventProximityDevice :: MonadIO m => EventProximity -> Ptr Gdk.Device.Device -> m ()
setEventProximityDevice s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (val :: Ptr Gdk.Device.Device)
clearEventProximityDevice :: MonadIO m => EventProximity -> m ()
clearEventProximityDevice s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (FP.nullPtr :: Ptr Gdk.Device.Device)
#if ENABLE_OVERLOADING
data EventProximityDeviceFieldInfo
instance AttrInfo EventProximityDeviceFieldInfo where
type AttrAllowedOps EventProximityDeviceFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventProximityDeviceFieldInfo = (~) (Ptr Gdk.Device.Device)
type AttrBaseTypeConstraint EventProximityDeviceFieldInfo = (~) EventProximity
type AttrGetType EventProximityDeviceFieldInfo = Maybe Gdk.Device.Device
type AttrLabel EventProximityDeviceFieldInfo = "device"
type AttrOrigin EventProximityDeviceFieldInfo = EventProximity
attrGet _ = getEventProximityDevice
attrSet _ = setEventProximityDevice
attrConstruct = undefined
attrClear _ = clearEventProximityDevice
eventProximity_device :: AttrLabelProxy "device"
eventProximity_device = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList EventProximity
type instance O.AttributeList EventProximity = EventProximityAttributeList
type EventProximityAttributeList = ('[ '("type", EventProximityTypeFieldInfo), '("window", EventProximityWindowFieldInfo), '("sendEvent", EventProximitySendEventFieldInfo), '("time", EventProximityTimeFieldInfo), '("device", EventProximityDeviceFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveEventProximityMethod (t :: Symbol) (o :: *) :: * where
ResolveEventProximityMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventProximityMethod t EventProximity, O.MethodInfo info EventProximity p) => OL.IsLabel t (EventProximity -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif