#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gdk.Structs.EventAny
(
EventAny(..) ,
newZeroEventAny ,
noEventAny ,
#if ENABLE_OVERLOADING
eventAny_sendEvent ,
#endif
getEventAnySendEvent ,
setEventAnySendEvent ,
#if ENABLE_OVERLOADING
eventAny_type ,
#endif
getEventAnyType ,
setEventAnyType ,
clearEventAnyWindow ,
#if ENABLE_OVERLOADING
eventAny_window ,
#endif
getEventAnyWindow ,
setEventAnyWindow ,
) 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
newtype EventAny = EventAny (ManagedPtr EventAny)
instance WrappedPtr EventAny where
wrappedPtrCalloc = callocBytes 24
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 24 >=> wrapPtr EventAny)
wrappedPtrFree = Just ptr_to_g_free
newZeroEventAny :: MonadIO m => m EventAny
newZeroEventAny = liftIO $ wrappedPtrCalloc >>= wrapPtr EventAny
instance tag ~ 'AttrSet => Constructible EventAny tag where
new _ attrs = do
o <- newZeroEventAny
GI.Attributes.set o attrs
return o
noEventAny :: Maybe EventAny
noEventAny = Nothing
getEventAnyType :: MonadIO m => EventAny -> m Gdk.Enums.EventType
getEventAnyType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setEventAnyType :: MonadIO m => EventAny -> Gdk.Enums.EventType -> m ()
setEventAnyType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 0) (val' :: CUInt)
#if ENABLE_OVERLOADING
data EventAnyTypeFieldInfo
instance AttrInfo EventAnyTypeFieldInfo where
type AttrAllowedOps EventAnyTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventAnyTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrBaseTypeConstraint EventAnyTypeFieldInfo = (~) EventAny
type AttrGetType EventAnyTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventAnyTypeFieldInfo = "type"
type AttrOrigin EventAnyTypeFieldInfo = EventAny
attrGet _ = getEventAnyType
attrSet _ = setEventAnyType
attrConstruct = undefined
attrClear _ = undefined
eventAny_type :: AttrLabelProxy "type"
eventAny_type = AttrLabelProxy
#endif
getEventAnyWindow :: MonadIO m => EventAny -> m (Maybe Gdk.Window.Window)
getEventAnyWindow 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
setEventAnyWindow :: MonadIO m => EventAny -> Ptr Gdk.Window.Window -> m ()
setEventAnyWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventAnyWindow :: MonadIO m => EventAny -> m ()
clearEventAnyWindow s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
#if ENABLE_OVERLOADING
data EventAnyWindowFieldInfo
instance AttrInfo EventAnyWindowFieldInfo where
type AttrAllowedOps EventAnyWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventAnyWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrBaseTypeConstraint EventAnyWindowFieldInfo = (~) EventAny
type AttrGetType EventAnyWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventAnyWindowFieldInfo = "window"
type AttrOrigin EventAnyWindowFieldInfo = EventAny
attrGet _ = getEventAnyWindow
attrSet _ = setEventAnyWindow
attrConstruct = undefined
attrClear _ = clearEventAnyWindow
eventAny_window :: AttrLabelProxy "window"
eventAny_window = AttrLabelProxy
#endif
getEventAnySendEvent :: MonadIO m => EventAny -> m Int8
getEventAnySendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int8
return val
setEventAnySendEvent :: MonadIO m => EventAny -> Int8 -> m ()
setEventAnySendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int8)
#if ENABLE_OVERLOADING
data EventAnySendEventFieldInfo
instance AttrInfo EventAnySendEventFieldInfo where
type AttrAllowedOps EventAnySendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventAnySendEventFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventAnySendEventFieldInfo = (~) EventAny
type AttrGetType EventAnySendEventFieldInfo = Int8
type AttrLabel EventAnySendEventFieldInfo = "send_event"
type AttrOrigin EventAnySendEventFieldInfo = EventAny
attrGet _ = getEventAnySendEvent
attrSet _ = setEventAnySendEvent
attrConstruct = undefined
attrClear _ = undefined
eventAny_sendEvent :: AttrLabelProxy "sendEvent"
eventAny_sendEvent = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList EventAny
type instance O.AttributeList EventAny = EventAnyAttributeList
type EventAnyAttributeList = ('[ '("type", EventAnyTypeFieldInfo), '("window", EventAnyWindowFieldInfo), '("sendEvent", EventAnySendEventFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveEventAnyMethod (t :: Symbol) (o :: *) :: * where
ResolveEventAnyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventAnyMethod t EventAny, O.MethodInfo info EventAny p) => O.IsLabelProxy t (EventAny -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveEventAnyMethod t EventAny, O.MethodInfo info EventAny p) => O.IsLabel t (EventAny -> 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
#endif