#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gdk.Structs.EventDND
(
EventDND(..) ,
newZeroEventDND ,
noEventDND ,
clearEventDNDContext ,
#if ENABLE_OVERLOADING
eventDND_context ,
#endif
getEventDNDContext ,
setEventDNDContext ,
#if ENABLE_OVERLOADING
eventDND_sendEvent ,
#endif
getEventDNDSendEvent ,
setEventDNDSendEvent ,
#if ENABLE_OVERLOADING
eventDND_time ,
#endif
getEventDNDTime ,
setEventDNDTime ,
#if ENABLE_OVERLOADING
eventDND_type ,
#endif
getEventDNDType ,
setEventDNDType ,
clearEventDNDWindow ,
#if ENABLE_OVERLOADING
eventDND_window ,
#endif
getEventDNDWindow ,
setEventDNDWindow ,
#if ENABLE_OVERLOADING
eventDND_xRoot ,
#endif
getEventDNDXRoot ,
setEventDNDXRoot ,
#if ENABLE_OVERLOADING
eventDND_yRoot ,
#endif
getEventDNDYRoot ,
setEventDNDYRoot ,
) 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.DragContext as Gdk.DragContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
newtype EventDND = EventDND (ManagedPtr EventDND)
instance WrappedPtr EventDND where
wrappedPtrCalloc = callocBytes 40
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 40 >=> wrapPtr EventDND)
wrappedPtrFree = Just ptr_to_g_free
newZeroEventDND :: MonadIO m => m EventDND
newZeroEventDND = liftIO $ wrappedPtrCalloc >>= wrapPtr EventDND
instance tag ~ 'AttrSet => Constructible EventDND tag where
new _ attrs = do
o <- newZeroEventDND
GI.Attributes.set o attrs
return o
noEventDND :: Maybe EventDND
noEventDND = Nothing
getEventDNDType :: MonadIO m => EventDND -> m Gdk.Enums.EventType
getEventDNDType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CInt
let val' = (toEnum . fromIntegral) val
return val'
setEventDNDType :: MonadIO m => EventDND -> Gdk.Enums.EventType -> m ()
setEventDNDType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 0) (val' :: CInt)
#if ENABLE_OVERLOADING
data EventDNDTypeFieldInfo
instance AttrInfo EventDNDTypeFieldInfo where
type AttrAllowedOps EventDNDTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventDNDTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrBaseTypeConstraint EventDNDTypeFieldInfo = (~) EventDND
type AttrGetType EventDNDTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventDNDTypeFieldInfo = "type"
type AttrOrigin EventDNDTypeFieldInfo = EventDND
attrGet _ = getEventDNDType
attrSet _ = setEventDNDType
attrConstruct = undefined
attrClear _ = undefined
eventDND_type :: AttrLabelProxy "type"
eventDND_type = AttrLabelProxy
#endif
getEventDNDWindow :: MonadIO m => EventDND -> m (Maybe Gdk.Window.Window)
getEventDNDWindow 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
setEventDNDWindow :: MonadIO m => EventDND -> Ptr Gdk.Window.Window -> m ()
setEventDNDWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventDNDWindow :: MonadIO m => EventDND -> m ()
clearEventDNDWindow s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
#if ENABLE_OVERLOADING
data EventDNDWindowFieldInfo
instance AttrInfo EventDNDWindowFieldInfo where
type AttrAllowedOps EventDNDWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventDNDWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrBaseTypeConstraint EventDNDWindowFieldInfo = (~) EventDND
type AttrGetType EventDNDWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventDNDWindowFieldInfo = "window"
type AttrOrigin EventDNDWindowFieldInfo = EventDND
attrGet _ = getEventDNDWindow
attrSet _ = setEventDNDWindow
attrConstruct = undefined
attrClear _ = clearEventDNDWindow
eventDND_window :: AttrLabelProxy "window"
eventDND_window = AttrLabelProxy
#endif
getEventDNDSendEvent :: MonadIO m => EventDND -> m Int8
getEventDNDSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int8
return val
setEventDNDSendEvent :: MonadIO m => EventDND -> Int8 -> m ()
setEventDNDSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int8)
#if ENABLE_OVERLOADING
data EventDNDSendEventFieldInfo
instance AttrInfo EventDNDSendEventFieldInfo where
type AttrAllowedOps EventDNDSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventDNDSendEventFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventDNDSendEventFieldInfo = (~) EventDND
type AttrGetType EventDNDSendEventFieldInfo = Int8
type AttrLabel EventDNDSendEventFieldInfo = "send_event"
type AttrOrigin EventDNDSendEventFieldInfo = EventDND
attrGet _ = getEventDNDSendEvent
attrSet _ = setEventDNDSendEvent
attrConstruct = undefined
attrClear _ = undefined
eventDND_sendEvent :: AttrLabelProxy "sendEvent"
eventDND_sendEvent = AttrLabelProxy
#endif
getEventDNDContext :: MonadIO m => EventDND -> m (Maybe Gdk.DragContext.DragContext)
getEventDNDContext s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO (Ptr Gdk.DragContext.DragContext)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.DragContext.DragContext) val'
return val''
return result
setEventDNDContext :: MonadIO m => EventDND -> Ptr Gdk.DragContext.DragContext -> m ()
setEventDNDContext s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (val :: Ptr Gdk.DragContext.DragContext)
clearEventDNDContext :: MonadIO m => EventDND -> m ()
clearEventDNDContext s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (FP.nullPtr :: Ptr Gdk.DragContext.DragContext)
#if ENABLE_OVERLOADING
data EventDNDContextFieldInfo
instance AttrInfo EventDNDContextFieldInfo where
type AttrAllowedOps EventDNDContextFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventDNDContextFieldInfo = (~) (Ptr Gdk.DragContext.DragContext)
type AttrBaseTypeConstraint EventDNDContextFieldInfo = (~) EventDND
type AttrGetType EventDNDContextFieldInfo = Maybe Gdk.DragContext.DragContext
type AttrLabel EventDNDContextFieldInfo = "context"
type AttrOrigin EventDNDContextFieldInfo = EventDND
attrGet _ = getEventDNDContext
attrSet _ = setEventDNDContext
attrConstruct = undefined
attrClear _ = clearEventDNDContext
eventDND_context :: AttrLabelProxy "context"
eventDND_context = AttrLabelProxy
#endif
getEventDNDTime :: MonadIO m => EventDND -> m Word32
getEventDNDTime s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO Word32
return val
setEventDNDTime :: MonadIO m => EventDND -> Word32 -> m ()
setEventDNDTime s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (val :: Word32)
#if ENABLE_OVERLOADING
data EventDNDTimeFieldInfo
instance AttrInfo EventDNDTimeFieldInfo where
type AttrAllowedOps EventDNDTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventDNDTimeFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventDNDTimeFieldInfo = (~) EventDND
type AttrGetType EventDNDTimeFieldInfo = Word32
type AttrLabel EventDNDTimeFieldInfo = "time"
type AttrOrigin EventDNDTimeFieldInfo = EventDND
attrGet _ = getEventDNDTime
attrSet _ = setEventDNDTime
attrConstruct = undefined
attrClear _ = undefined
eventDND_time :: AttrLabelProxy "time"
eventDND_time = AttrLabelProxy
#endif
getEventDNDXRoot :: MonadIO m => EventDND -> m Int16
getEventDNDXRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 36) :: IO Int16
return val
setEventDNDXRoot :: MonadIO m => EventDND -> Int16 -> m ()
setEventDNDXRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 36) (val :: Int16)
#if ENABLE_OVERLOADING
data EventDNDXRootFieldInfo
instance AttrInfo EventDNDXRootFieldInfo where
type AttrAllowedOps EventDNDXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventDNDXRootFieldInfo = (~) Int16
type AttrBaseTypeConstraint EventDNDXRootFieldInfo = (~) EventDND
type AttrGetType EventDNDXRootFieldInfo = Int16
type AttrLabel EventDNDXRootFieldInfo = "x_root"
type AttrOrigin EventDNDXRootFieldInfo = EventDND
attrGet _ = getEventDNDXRoot
attrSet _ = setEventDNDXRoot
attrConstruct = undefined
attrClear _ = undefined
eventDND_xRoot :: AttrLabelProxy "xRoot"
eventDND_xRoot = AttrLabelProxy
#endif
getEventDNDYRoot :: MonadIO m => EventDND -> m Int16
getEventDNDYRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 38) :: IO Int16
return val
setEventDNDYRoot :: MonadIO m => EventDND -> Int16 -> m ()
setEventDNDYRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 38) (val :: Int16)
#if ENABLE_OVERLOADING
data EventDNDYRootFieldInfo
instance AttrInfo EventDNDYRootFieldInfo where
type AttrAllowedOps EventDNDYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventDNDYRootFieldInfo = (~) Int16
type AttrBaseTypeConstraint EventDNDYRootFieldInfo = (~) EventDND
type AttrGetType EventDNDYRootFieldInfo = Int16
type AttrLabel EventDNDYRootFieldInfo = "y_root"
type AttrOrigin EventDNDYRootFieldInfo = EventDND
attrGet _ = getEventDNDYRoot
attrSet _ = setEventDNDYRoot
attrConstruct = undefined
attrClear _ = undefined
eventDND_yRoot :: AttrLabelProxy "yRoot"
eventDND_yRoot = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList EventDND
type instance O.AttributeList EventDND = EventDNDAttributeList
type EventDNDAttributeList = ('[ '("type", EventDNDTypeFieldInfo), '("window", EventDNDWindowFieldInfo), '("sendEvent", EventDNDSendEventFieldInfo), '("context", EventDNDContextFieldInfo), '("time", EventDNDTimeFieldInfo), '("xRoot", EventDNDXRootFieldInfo), '("yRoot", EventDNDYRootFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveEventDNDMethod (t :: Symbol) (o :: *) :: * where
ResolveEventDNDMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventDNDMethod t EventDND, O.MethodInfo info EventDND p) => OL.IsLabel t (EventDND -> 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