{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gdk.Objects.DragContext
    ( 

-- * Exported types
    DragContext(..)                         ,
    IsDragContext                           ,
    toDragContext                           ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDragContextMethod                ,
#endif


-- ** getActions #method:getActions#

#if defined(ENABLE_OVERLOADING)
    DragContextGetActionsMethodInfo         ,
#endif
    dragContextGetActions                   ,


-- ** getDestWindow #method:getDestWindow#

#if defined(ENABLE_OVERLOADING)
    DragContextGetDestWindowMethodInfo      ,
#endif
    dragContextGetDestWindow                ,


-- ** getDevice #method:getDevice#

#if defined(ENABLE_OVERLOADING)
    DragContextGetDeviceMethodInfo          ,
#endif
    dragContextGetDevice                    ,


-- ** getDragWindow #method:getDragWindow#

#if defined(ENABLE_OVERLOADING)
    DragContextGetDragWindowMethodInfo      ,
#endif
    dragContextGetDragWindow                ,


-- ** getProtocol #method:getProtocol#

#if defined(ENABLE_OVERLOADING)
    DragContextGetProtocolMethodInfo        ,
#endif
    dragContextGetProtocol                  ,


-- ** getSelectedAction #method:getSelectedAction#

#if defined(ENABLE_OVERLOADING)
    DragContextGetSelectedActionMethodInfo  ,
#endif
    dragContextGetSelectedAction            ,


-- ** getSourceWindow #method:getSourceWindow#

#if defined(ENABLE_OVERLOADING)
    DragContextGetSourceWindowMethodInfo    ,
#endif
    dragContextGetSourceWindow              ,


-- ** getSuggestedAction #method:getSuggestedAction#

#if defined(ENABLE_OVERLOADING)
    DragContextGetSuggestedActionMethodInfo ,
#endif
    dragContextGetSuggestedAction           ,


-- ** listTargets #method:listTargets#

#if defined(ENABLE_OVERLOADING)
    DragContextListTargetsMethodInfo        ,
#endif
    dragContextListTargets                  ,


-- ** manageDnd #method:manageDnd#

#if defined(ENABLE_OVERLOADING)
    DragContextManageDndMethodInfo          ,
#endif
    dragContextManageDnd                    ,


-- ** setDevice #method:setDevice#

#if defined(ENABLE_OVERLOADING)
    DragContextSetDeviceMethodInfo          ,
#endif
    dragContextSetDevice                    ,


-- ** setHotspot #method:setHotspot#

#if defined(ENABLE_OVERLOADING)
    DragContextSetHotspotMethodInfo         ,
#endif
    dragContextSetHotspot                   ,




 -- * Signals
-- ** actionChanged #signal:actionChanged#

    C_DragContextActionChangedCallback      ,
    DragContextActionChangedCallback        ,
#if defined(ENABLE_OVERLOADING)
    DragContextActionChangedSignalInfo      ,
#endif
    afterDragContextActionChanged           ,
    genClosure_DragContextActionChanged     ,
    mk_DragContextActionChangedCallback     ,
    noDragContextActionChangedCallback      ,
    onDragContextActionChanged              ,
    wrap_DragContextActionChangedCallback   ,


-- ** cancel #signal:cancel#

    C_DragContextCancelCallback             ,
    DragContextCancelCallback               ,
#if defined(ENABLE_OVERLOADING)
    DragContextCancelSignalInfo             ,
#endif
    afterDragContextCancel                  ,
    genClosure_DragContextCancel            ,
    mk_DragContextCancelCallback            ,
    noDragContextCancelCallback             ,
    onDragContextCancel                     ,
    wrap_DragContextCancelCallback          ,


-- ** dndFinished #signal:dndFinished#

    C_DragContextDndFinishedCallback        ,
    DragContextDndFinishedCallback          ,
#if defined(ENABLE_OVERLOADING)
    DragContextDndFinishedSignalInfo        ,
#endif
    afterDragContextDndFinished             ,
    genClosure_DragContextDndFinished       ,
    mk_DragContextDndFinishedCallback       ,
    noDragContextDndFinishedCallback        ,
    onDragContextDndFinished                ,
    wrap_DragContextDndFinishedCallback     ,


-- ** dropPerformed #signal:dropPerformed#

    C_DragContextDropPerformedCallback      ,
    DragContextDropPerformedCallback        ,
#if defined(ENABLE_OVERLOADING)
    DragContextDropPerformedSignalInfo      ,
#endif
    afterDragContextDropPerformed           ,
    genClosure_DragContextDropPerformed     ,
    mk_DragContextDropPerformedCallback     ,
    noDragContextDropPerformedCallback      ,
    onDragContextDropPerformed              ,
    wrap_DragContextDropPerformedCallback   ,




    ) 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.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.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 GI.GObject.Objects.Object as GObject.Object
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
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom

-- | Memory-managed wrapper type.
newtype DragContext = DragContext (SP.ManagedPtr DragContext)
    deriving (DragContext -> DragContext -> Bool
(DragContext -> DragContext -> Bool)
-> (DragContext -> DragContext -> Bool) -> Eq DragContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DragContext -> DragContext -> Bool
$c/= :: DragContext -> DragContext -> Bool
== :: DragContext -> DragContext -> Bool
$c== :: DragContext -> DragContext -> Bool
Eq)

instance SP.ManagedPtrNewtype DragContext where
    toManagedPtr :: DragContext -> ManagedPtr DragContext
toManagedPtr (DragContext ManagedPtr DragContext
p) = ManagedPtr DragContext
p

foreign import ccall "gdk_drag_context_get_type"
    c_gdk_drag_context_get_type :: IO B.Types.GType

instance B.Types.TypedObject DragContext where
    glibType :: IO GType
glibType = IO GType
c_gdk_drag_context_get_type

instance B.Types.GObject DragContext

-- | Convert 'DragContext' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DragContext where
    toGValue :: DragContext -> IO GValue
toGValue DragContext
o = do
        GType
gtype <- IO GType
c_gdk_drag_context_get_type
        DragContext -> (Ptr DragContext -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DragContext
o (GType
-> (GValue -> Ptr DragContext -> IO ())
-> Ptr DragContext
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DragContext -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DragContext
fromGValue GValue
gv = do
        Ptr DragContext
ptr <- GValue -> IO (Ptr DragContext)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DragContext)
        (ManagedPtr DragContext -> DragContext)
-> Ptr DragContext -> IO DragContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DragContext -> DragContext
DragContext Ptr DragContext
ptr
        
    

-- | Type class for types which can be safely cast to `DragContext`, for instance with `toDragContext`.
class (SP.GObject o, O.IsDescendantOf DragContext o) => IsDragContext o
instance (SP.GObject o, O.IsDescendantOf DragContext o) => IsDragContext o

instance O.HasParentTypes DragContext
type instance O.ParentTypes DragContext = '[GObject.Object.Object]

-- | Cast to `DragContext`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDragContext :: (MonadIO m, IsDragContext o) => o -> m DragContext
toDragContext :: o -> m DragContext
toDragContext = IO DragContext -> m DragContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DragContext -> m DragContext)
-> (o -> IO DragContext) -> o -> m DragContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DragContext -> DragContext) -> o -> IO DragContext
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DragContext -> DragContext
DragContext

#if defined(ENABLE_OVERLOADING)
type family ResolveDragContextMethod (t :: Symbol) (o :: *) :: * where
    ResolveDragContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDragContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDragContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDragContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDragContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDragContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDragContextMethod "listTargets" o = DragContextListTargetsMethodInfo
    ResolveDragContextMethod "manageDnd" o = DragContextManageDndMethodInfo
    ResolveDragContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDragContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDragContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDragContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDragContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDragContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDragContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDragContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDragContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDragContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDragContextMethod "getActions" o = DragContextGetActionsMethodInfo
    ResolveDragContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDragContextMethod "getDestWindow" o = DragContextGetDestWindowMethodInfo
    ResolveDragContextMethod "getDevice" o = DragContextGetDeviceMethodInfo
    ResolveDragContextMethod "getDragWindow" o = DragContextGetDragWindowMethodInfo
    ResolveDragContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDragContextMethod "getProtocol" o = DragContextGetProtocolMethodInfo
    ResolveDragContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDragContextMethod "getSelectedAction" o = DragContextGetSelectedActionMethodInfo
    ResolveDragContextMethod "getSourceWindow" o = DragContextGetSourceWindowMethodInfo
    ResolveDragContextMethod "getSuggestedAction" o = DragContextGetSuggestedActionMethodInfo
    ResolveDragContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDragContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDragContextMethod "setDevice" o = DragContextSetDeviceMethodInfo
    ResolveDragContextMethod "setHotspot" o = DragContextSetHotspotMethodInfo
    ResolveDragContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDragContextMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDragContextMethod t DragContext, O.MethodInfo info DragContext p) => OL.IsLabel t (DragContext -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal DragContext::action-changed
-- | A new action is being chosen for the drag and drop operation.
-- 
-- This signal will only be emitted if the t'GI.Gdk.Objects.DragContext.DragContext' manages
-- the drag and drop operation. See 'GI.Gdk.Objects.DragContext.dragContextManageDnd'
-- for more information.
-- 
-- /Since: 3.20/
type DragContextActionChangedCallback =
    [Gdk.Flags.DragAction]
    -- ^ /@action@/: The action currently chosen
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DragContextActionChangedCallback`@.
noDragContextActionChangedCallback :: Maybe DragContextActionChangedCallback
noDragContextActionChangedCallback :: Maybe DragContextActionChangedCallback
noDragContextActionChangedCallback = Maybe DragContextActionChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DragContextActionChangedCallback =
    Ptr () ->                               -- object
    CUInt ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DragContextActionChangedCallback`.
foreign import ccall "wrapper"
    mk_DragContextActionChangedCallback :: C_DragContextActionChangedCallback -> IO (FunPtr C_DragContextActionChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DragContextActionChanged :: MonadIO m => DragContextActionChangedCallback -> m (GClosure C_DragContextActionChangedCallback)
genClosure_DragContextActionChanged :: DragContextActionChangedCallback
-> m (GClosure C_DragContextActionChangedCallback)
genClosure_DragContextActionChanged DragContextActionChangedCallback
cb = IO (GClosure C_DragContextActionChangedCallback)
-> m (GClosure C_DragContextActionChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DragContextActionChangedCallback)
 -> m (GClosure C_DragContextActionChangedCallback))
-> IO (GClosure C_DragContextActionChangedCallback)
-> m (GClosure C_DragContextActionChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextActionChangedCallback
cb' = DragContextActionChangedCallback
-> C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback DragContextActionChangedCallback
cb
    C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextActionChangedCallback C_DragContextActionChangedCallback
cb' IO (FunPtr C_DragContextActionChangedCallback)
-> (FunPtr C_DragContextActionChangedCallback
    -> IO (GClosure C_DragContextActionChangedCallback))
-> IO (GClosure C_DragContextActionChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DragContextActionChangedCallback
-> IO (GClosure C_DragContextActionChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DragContextActionChangedCallback` into a `C_DragContextActionChangedCallback`.
wrap_DragContextActionChangedCallback ::
    DragContextActionChangedCallback ->
    C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback :: DragContextActionChangedCallback
-> C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback DragContextActionChangedCallback
_cb Ptr ()
_ CUInt
action Ptr ()
_ = do
    let action' :: [DragAction]
action' = CUInt -> [DragAction]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
action
    DragContextActionChangedCallback
_cb  [DragAction]
action'


-- | Connect a signal handler for the [actionChanged](#signal:actionChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dragContext #actionChanged callback
-- @
-- 
-- 
onDragContextActionChanged :: (IsDragContext a, MonadIO m) => a -> DragContextActionChangedCallback -> m SignalHandlerId
onDragContextActionChanged :: a -> DragContextActionChangedCallback -> m SignalHandlerId
onDragContextActionChanged a
obj DragContextActionChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextActionChangedCallback
cb' = DragContextActionChangedCallback
-> C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback DragContextActionChangedCallback
cb
    FunPtr C_DragContextActionChangedCallback
cb'' <- C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextActionChangedCallback C_DragContextActionChangedCallback
cb'
    a
-> Text
-> FunPtr C_DragContextActionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"action-changed" FunPtr C_DragContextActionChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [actionChanged](#signal:actionChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dragContext #actionChanged callback
-- @
-- 
-- 
afterDragContextActionChanged :: (IsDragContext a, MonadIO m) => a -> DragContextActionChangedCallback -> m SignalHandlerId
afterDragContextActionChanged :: a -> DragContextActionChangedCallback -> m SignalHandlerId
afterDragContextActionChanged a
obj DragContextActionChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextActionChangedCallback
cb' = DragContextActionChangedCallback
-> C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback DragContextActionChangedCallback
cb
    FunPtr C_DragContextActionChangedCallback
cb'' <- C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextActionChangedCallback C_DragContextActionChangedCallback
cb'
    a
-> Text
-> FunPtr C_DragContextActionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"action-changed" FunPtr C_DragContextActionChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DragContextActionChangedSignalInfo
instance SignalInfo DragContextActionChangedSignalInfo where
    type HaskellCallbackType DragContextActionChangedSignalInfo = DragContextActionChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DragContextActionChangedCallback cb
        cb'' <- mk_DragContextActionChangedCallback cb'
        connectSignalFunPtr obj "action-changed" cb'' connectMode detail

#endif

-- signal DragContext::cancel
-- | The drag and drop operation was cancelled.
-- 
-- This signal will only be emitted if the t'GI.Gdk.Objects.DragContext.DragContext' manages
-- the drag and drop operation. See 'GI.Gdk.Objects.DragContext.dragContextManageDnd'
-- for more information.
-- 
-- /Since: 3.20/
type DragContextCancelCallback =
    Gdk.Enums.DragCancelReason
    -- ^ /@reason@/: The reason the context was cancelled
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DragContextCancelCallback`@.
noDragContextCancelCallback :: Maybe DragContextCancelCallback
noDragContextCancelCallback :: Maybe DragContextCancelCallback
noDragContextCancelCallback = Maybe DragContextCancelCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DragContextCancelCallback =
    Ptr () ->                               -- object
    CUInt ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DragContextCancelCallback`.
foreign import ccall "wrapper"
    mk_DragContextCancelCallback :: C_DragContextCancelCallback -> IO (FunPtr C_DragContextCancelCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DragContextCancel :: MonadIO m => DragContextCancelCallback -> m (GClosure C_DragContextCancelCallback)
genClosure_DragContextCancel :: DragContextCancelCallback
-> m (GClosure C_DragContextActionChangedCallback)
genClosure_DragContextCancel DragContextCancelCallback
cb = IO (GClosure C_DragContextActionChangedCallback)
-> m (GClosure C_DragContextActionChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DragContextActionChangedCallback)
 -> m (GClosure C_DragContextActionChangedCallback))
-> IO (GClosure C_DragContextActionChangedCallback)
-> m (GClosure C_DragContextActionChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextActionChangedCallback
cb' = DragContextCancelCallback -> C_DragContextActionChangedCallback
wrap_DragContextCancelCallback DragContextCancelCallback
cb
    C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextCancelCallback C_DragContextActionChangedCallback
cb' IO (FunPtr C_DragContextActionChangedCallback)
-> (FunPtr C_DragContextActionChangedCallback
    -> IO (GClosure C_DragContextActionChangedCallback))
-> IO (GClosure C_DragContextActionChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DragContextActionChangedCallback
-> IO (GClosure C_DragContextActionChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DragContextCancelCallback` into a `C_DragContextCancelCallback`.
wrap_DragContextCancelCallback ::
    DragContextCancelCallback ->
    C_DragContextCancelCallback
wrap_DragContextCancelCallback :: DragContextCancelCallback -> C_DragContextActionChangedCallback
wrap_DragContextCancelCallback DragContextCancelCallback
_cb Ptr ()
_ CUInt
reason Ptr ()
_ = do
    let reason' :: DragCancelReason
reason' = (Int -> DragCancelReason
forall a. Enum a => Int -> a
toEnum (Int -> DragCancelReason)
-> (CUInt -> Int) -> CUInt -> DragCancelReason
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
reason
    DragContextCancelCallback
_cb  DragCancelReason
reason'


-- | Connect a signal handler for the [cancel](#signal:cancel) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dragContext #cancel callback
-- @
-- 
-- 
onDragContextCancel :: (IsDragContext a, MonadIO m) => a -> DragContextCancelCallback -> m SignalHandlerId
onDragContextCancel :: a -> DragContextCancelCallback -> m SignalHandlerId
onDragContextCancel a
obj DragContextCancelCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextActionChangedCallback
cb' = DragContextCancelCallback -> C_DragContextActionChangedCallback
wrap_DragContextCancelCallback DragContextCancelCallback
cb
    FunPtr C_DragContextActionChangedCallback
cb'' <- C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextCancelCallback C_DragContextActionChangedCallback
cb'
    a
-> Text
-> FunPtr C_DragContextActionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"cancel" FunPtr C_DragContextActionChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [cancel](#signal:cancel) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dragContext #cancel callback
-- @
-- 
-- 
afterDragContextCancel :: (IsDragContext a, MonadIO m) => a -> DragContextCancelCallback -> m SignalHandlerId
afterDragContextCancel :: a -> DragContextCancelCallback -> m SignalHandlerId
afterDragContextCancel a
obj DragContextCancelCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextActionChangedCallback
cb' = DragContextCancelCallback -> C_DragContextActionChangedCallback
wrap_DragContextCancelCallback DragContextCancelCallback
cb
    FunPtr C_DragContextActionChangedCallback
cb'' <- C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextCancelCallback C_DragContextActionChangedCallback
cb'
    a
-> Text
-> FunPtr C_DragContextActionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"cancel" FunPtr C_DragContextActionChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DragContextCancelSignalInfo
instance SignalInfo DragContextCancelSignalInfo where
    type HaskellCallbackType DragContextCancelSignalInfo = DragContextCancelCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DragContextCancelCallback cb
        cb'' <- mk_DragContextCancelCallback cb'
        connectSignalFunPtr obj "cancel" cb'' connectMode detail

#endif

-- signal DragContext::dnd-finished
-- | The drag and drop operation was finished, the drag destination
-- finished reading all data. The drag source can now free all
-- miscellaneous data.
-- 
-- This signal will only be emitted if the t'GI.Gdk.Objects.DragContext.DragContext' manages
-- the drag and drop operation. See 'GI.Gdk.Objects.DragContext.dragContextManageDnd'
-- for more information.
-- 
-- /Since: 3.20/
type DragContextDndFinishedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DragContextDndFinishedCallback`@.
noDragContextDndFinishedCallback :: Maybe DragContextDndFinishedCallback
noDragContextDndFinishedCallback :: Maybe (IO ())
noDragContextDndFinishedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DragContextDndFinishedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DragContextDndFinishedCallback`.
foreign import ccall "wrapper"
    mk_DragContextDndFinishedCallback :: C_DragContextDndFinishedCallback -> IO (FunPtr C_DragContextDndFinishedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DragContextDndFinished :: MonadIO m => DragContextDndFinishedCallback -> m (GClosure C_DragContextDndFinishedCallback)
genClosure_DragContextDndFinished :: IO () -> m (GClosure C_DragContextDndFinishedCallback)
genClosure_DragContextDndFinished IO ()
cb = IO (GClosure C_DragContextDndFinishedCallback)
-> m (GClosure C_DragContextDndFinishedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DragContextDndFinishedCallback)
 -> m (GClosure C_DragContextDndFinishedCallback))
-> IO (GClosure C_DragContextDndFinishedCallback)
-> m (GClosure C_DragContextDndFinishedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextDndFinishedCallback
cb' = IO () -> C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback IO ()
cb
    C_DragContextDndFinishedCallback
-> IO (FunPtr C_DragContextDndFinishedCallback)
mk_DragContextDndFinishedCallback C_DragContextDndFinishedCallback
cb' IO (FunPtr C_DragContextDndFinishedCallback)
-> (FunPtr C_DragContextDndFinishedCallback
    -> IO (GClosure C_DragContextDndFinishedCallback))
-> IO (GClosure C_DragContextDndFinishedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DragContextDndFinishedCallback
-> IO (GClosure C_DragContextDndFinishedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DragContextDndFinishedCallback` into a `C_DragContextDndFinishedCallback`.
wrap_DragContextDndFinishedCallback ::
    DragContextDndFinishedCallback ->
    C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback :: IO () -> C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [dndFinished](#signal:dndFinished) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dragContext #dndFinished callback
-- @
-- 
-- 
onDragContextDndFinished :: (IsDragContext a, MonadIO m) => a -> DragContextDndFinishedCallback -> m SignalHandlerId
onDragContextDndFinished :: a -> IO () -> m SignalHandlerId
onDragContextDndFinished a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextDndFinishedCallback
cb' = IO () -> C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback IO ()
cb
    FunPtr C_DragContextDndFinishedCallback
cb'' <- C_DragContextDndFinishedCallback
-> IO (FunPtr C_DragContextDndFinishedCallback)
mk_DragContextDndFinishedCallback C_DragContextDndFinishedCallback
cb'
    a
-> Text
-> FunPtr C_DragContextDndFinishedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"dnd-finished" FunPtr C_DragContextDndFinishedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [dndFinished](#signal:dndFinished) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dragContext #dndFinished callback
-- @
-- 
-- 
afterDragContextDndFinished :: (IsDragContext a, MonadIO m) => a -> DragContextDndFinishedCallback -> m SignalHandlerId
afterDragContextDndFinished :: a -> IO () -> m SignalHandlerId
afterDragContextDndFinished a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextDndFinishedCallback
cb' = IO () -> C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback IO ()
cb
    FunPtr C_DragContextDndFinishedCallback
cb'' <- C_DragContextDndFinishedCallback
-> IO (FunPtr C_DragContextDndFinishedCallback)
mk_DragContextDndFinishedCallback C_DragContextDndFinishedCallback
cb'
    a
-> Text
-> FunPtr C_DragContextDndFinishedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"dnd-finished" FunPtr C_DragContextDndFinishedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DragContextDndFinishedSignalInfo
instance SignalInfo DragContextDndFinishedSignalInfo where
    type HaskellCallbackType DragContextDndFinishedSignalInfo = DragContextDndFinishedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DragContextDndFinishedCallback cb
        cb'' <- mk_DragContextDndFinishedCallback cb'
        connectSignalFunPtr obj "dnd-finished" cb'' connectMode detail

#endif

-- signal DragContext::drop-performed
-- | The drag and drop operation was performed on an accepting client.
-- 
-- This signal will only be emitted if the t'GI.Gdk.Objects.DragContext.DragContext' manages
-- the drag and drop operation. See 'GI.Gdk.Objects.DragContext.dragContextManageDnd'
-- for more information.
-- 
-- /Since: 3.20/
type DragContextDropPerformedCallback =
    Int32
    -- ^ /@time@/: the time at which the drop happened.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DragContextDropPerformedCallback`@.
noDragContextDropPerformedCallback :: Maybe DragContextDropPerformedCallback
noDragContextDropPerformedCallback :: Maybe DragContextDropPerformedCallback
noDragContextDropPerformedCallback = Maybe DragContextDropPerformedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DragContextDropPerformedCallback =
    Ptr () ->                               -- object
    Int32 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DragContextDropPerformedCallback`.
foreign import ccall "wrapper"
    mk_DragContextDropPerformedCallback :: C_DragContextDropPerformedCallback -> IO (FunPtr C_DragContextDropPerformedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DragContextDropPerformed :: MonadIO m => DragContextDropPerformedCallback -> m (GClosure C_DragContextDropPerformedCallback)
genClosure_DragContextDropPerformed :: DragContextDropPerformedCallback
-> m (GClosure C_DragContextDropPerformedCallback)
genClosure_DragContextDropPerformed DragContextDropPerformedCallback
cb = IO (GClosure C_DragContextDropPerformedCallback)
-> m (GClosure C_DragContextDropPerformedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DragContextDropPerformedCallback)
 -> m (GClosure C_DragContextDropPerformedCallback))
-> IO (GClosure C_DragContextDropPerformedCallback)
-> m (GClosure C_DragContextDropPerformedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextDropPerformedCallback
cb' = DragContextDropPerformedCallback
-> C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback DragContextDropPerformedCallback
cb
    C_DragContextDropPerformedCallback
-> IO (FunPtr C_DragContextDropPerformedCallback)
mk_DragContextDropPerformedCallback C_DragContextDropPerformedCallback
cb' IO (FunPtr C_DragContextDropPerformedCallback)
-> (FunPtr C_DragContextDropPerformedCallback
    -> IO (GClosure C_DragContextDropPerformedCallback))
-> IO (GClosure C_DragContextDropPerformedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DragContextDropPerformedCallback
-> IO (GClosure C_DragContextDropPerformedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DragContextDropPerformedCallback` into a `C_DragContextDropPerformedCallback`.
wrap_DragContextDropPerformedCallback ::
    DragContextDropPerformedCallback ->
    C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback :: DragContextDropPerformedCallback
-> C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback DragContextDropPerformedCallback
_cb Ptr ()
_ Int32
time Ptr ()
_ = do
    DragContextDropPerformedCallback
_cb  Int32
time


-- | Connect a signal handler for the [dropPerformed](#signal:dropPerformed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dragContext #dropPerformed callback
-- @
-- 
-- 
onDragContextDropPerformed :: (IsDragContext a, MonadIO m) => a -> DragContextDropPerformedCallback -> m SignalHandlerId
onDragContextDropPerformed :: a -> DragContextDropPerformedCallback -> m SignalHandlerId
onDragContextDropPerformed a
obj DragContextDropPerformedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextDropPerformedCallback
cb' = DragContextDropPerformedCallback
-> C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback DragContextDropPerformedCallback
cb
    FunPtr C_DragContextDropPerformedCallback
cb'' <- C_DragContextDropPerformedCallback
-> IO (FunPtr C_DragContextDropPerformedCallback)
mk_DragContextDropPerformedCallback C_DragContextDropPerformedCallback
cb'
    a
-> Text
-> FunPtr C_DragContextDropPerformedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"drop-performed" FunPtr C_DragContextDropPerformedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [dropPerformed](#signal:dropPerformed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dragContext #dropPerformed callback
-- @
-- 
-- 
afterDragContextDropPerformed :: (IsDragContext a, MonadIO m) => a -> DragContextDropPerformedCallback -> m SignalHandlerId
afterDragContextDropPerformed :: a -> DragContextDropPerformedCallback -> m SignalHandlerId
afterDragContextDropPerformed a
obj DragContextDropPerformedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DragContextDropPerformedCallback
cb' = DragContextDropPerformedCallback
-> C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback DragContextDropPerformedCallback
cb
    FunPtr C_DragContextDropPerformedCallback
cb'' <- C_DragContextDropPerformedCallback
-> IO (FunPtr C_DragContextDropPerformedCallback)
mk_DragContextDropPerformedCallback C_DragContextDropPerformedCallback
cb'
    a
-> Text
-> FunPtr C_DragContextDropPerformedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"drop-performed" FunPtr C_DragContextDropPerformedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DragContextDropPerformedSignalInfo
instance SignalInfo DragContextDropPerformedSignalInfo where
    type HaskellCallbackType DragContextDropPerformedSignalInfo = DragContextDropPerformedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DragContextDropPerformedCallback cb
        cb'' <- mk_DragContextDropPerformedCallback cb'
        connectSignalFunPtr obj "drop-performed" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DragContext
type instance O.AttributeList DragContext = DragContextAttributeList
type DragContextAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DragContext = DragContextSignalList
type DragContextSignalList = ('[ '("actionChanged", DragContextActionChangedSignalInfo), '("cancel", DragContextCancelSignalInfo), '("dndFinished", DragContextDndFinishedSignalInfo), '("dropPerformed", DragContextDropPerformedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method DragContext::get_actions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "DragAction" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_get_actions" gdk_drag_context_get_actions :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO CUInt

-- | Determines the bitmask of actions proposed by the source if
-- 'GI.Gdk.Objects.DragContext.dragContextGetSuggestedAction' returns 'GI.Gdk.Flags.DragActionAsk'.
-- 
-- /Since: 2.22/
dragContextGetActions ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m [Gdk.Flags.DragAction]
    -- ^ __Returns:__ the t'GI.Gdk.Flags.DragAction' flags
dragContextGetActions :: a -> m [DragAction]
dragContextGetActions a
context = IO [DragAction] -> m [DragAction]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DragAction] -> m [DragAction])
-> IO [DragAction] -> m [DragAction]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CUInt
result <- Ptr DragContext -> IO CUInt
gdk_drag_context_get_actions Ptr DragContext
context'
    let result' :: [DragAction]
result' = CUInt -> [DragAction]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    [DragAction] -> IO [DragAction]
forall (m :: * -> *) a. Monad m => a -> m a
return [DragAction]
result'

#if defined(ENABLE_OVERLOADING)
data DragContextGetActionsMethodInfo
instance (signature ~ (m [Gdk.Flags.DragAction]), MonadIO m, IsDragContext a) => O.MethodInfo DragContextGetActionsMethodInfo a signature where
    overloadedMethod = dragContextGetActions

#endif

-- method DragContext::get_dest_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_get_dest_window" gdk_drag_context_get_dest_window :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO (Ptr Gdk.Window.Window)

-- | Returns the destination window for the DND operation.
-- 
-- /Since: 3.0/
dragContextGetDestWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m Gdk.Window.Window
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Window.Window'
dragContextGetDestWindow :: a -> m Window
dragContextGetDestWindow a
context = IO Window -> m Window
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Window
result <- Ptr DragContext -> IO (Ptr Window)
gdk_drag_context_get_dest_window Ptr DragContext
context'
    Text -> Ptr Window -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dragContextGetDestWindow" Ptr Window
result
    Window
result' <- ((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
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result'

#if defined(ENABLE_OVERLOADING)
data DragContextGetDestWindowMethodInfo
instance (signature ~ (m Gdk.Window.Window), MonadIO m, IsDragContext a) => O.MethodInfo DragContextGetDestWindowMethodInfo a signature where
    overloadedMethod = dragContextGetDestWindow

#endif

-- method DragContext::get_device
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Device" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_get_device" gdk_drag_context_get_device :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO (Ptr Gdk.Device.Device)

-- | Returns the t'GI.Gdk.Objects.Device.Device' associated to the drag context.
dragContextGetDevice ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m Gdk.Device.Device
    -- ^ __Returns:__ The t'GI.Gdk.Objects.Device.Device' associated to /@context@/.
dragContextGetDevice :: a -> m Device
dragContextGetDevice a
context = IO Device -> m Device
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Device -> m Device) -> IO Device -> m Device
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Device
result <- Ptr DragContext -> IO (Ptr Device)
gdk_drag_context_get_device Ptr DragContext
context'
    Text -> Ptr Device -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dragContextGetDevice" Ptr Device
result
    Device
result' <- ((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
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Device -> IO Device
forall (m :: * -> *) a. Monad m => a -> m a
return Device
result'

#if defined(ENABLE_OVERLOADING)
data DragContextGetDeviceMethodInfo
instance (signature ~ (m Gdk.Device.Device), MonadIO m, IsDragContext a) => O.MethodInfo DragContextGetDeviceMethodInfo a signature where
    overloadedMethod = dragContextGetDevice

#endif

-- method DragContext::get_drag_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_get_drag_window" gdk_drag_context_get_drag_window :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO (Ptr Gdk.Window.Window)

-- | Returns the window on which the drag icon should be rendered
-- during the drag operation. Note that the window may not be
-- available until the drag operation has begun. GDK will move
-- the window in accordance with the ongoing drag operation.
-- The window is owned by /@context@/ and will be destroyed when
-- the drag operation is over.
-- 
-- /Since: 3.20/
dragContextGetDragWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m (Maybe Gdk.Window.Window)
    -- ^ __Returns:__ the drag window, or 'P.Nothing'
dragContextGetDragWindow :: a -> m (Maybe Window)
dragContextGetDragWindow a
context = 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
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Window
result <- Ptr DragContext -> IO (Ptr Window)
gdk_drag_context_get_drag_window Ptr DragContext
context'
    Maybe Window
maybeResult <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Window
result ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr Window
result' -> do
        Window
result'' <- ((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
result'
        Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
maybeResult

#if defined(ENABLE_OVERLOADING)
data DragContextGetDragWindowMethodInfo
instance (signature ~ (m (Maybe Gdk.Window.Window)), MonadIO m, IsDragContext a) => O.MethodInfo DragContextGetDragWindowMethodInfo a signature where
    overloadedMethod = dragContextGetDragWindow

#endif

-- method DragContext::get_protocol
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gdk" , name = "DragProtocol" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_get_protocol" gdk_drag_context_get_protocol :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO CUInt

-- | Returns the drag protocol that is used by this context.
-- 
-- /Since: 3.0/
dragContextGetProtocol ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m Gdk.Enums.DragProtocol
    -- ^ __Returns:__ the drag protocol
dragContextGetProtocol :: a -> m DragProtocol
dragContextGetProtocol a
context = IO DragProtocol -> m DragProtocol
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DragProtocol -> m DragProtocol)
-> IO DragProtocol -> m DragProtocol
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CUInt
result <- Ptr DragContext -> IO CUInt
gdk_drag_context_get_protocol Ptr DragContext
context'
    let result' :: DragProtocol
result' = (Int -> DragProtocol
forall a. Enum a => Int -> a
toEnum (Int -> DragProtocol) -> (CUInt -> Int) -> CUInt -> DragProtocol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    DragProtocol -> IO DragProtocol
forall (m :: * -> *) a. Monad m => a -> m a
return DragProtocol
result'

#if defined(ENABLE_OVERLOADING)
data DragContextGetProtocolMethodInfo
instance (signature ~ (m Gdk.Enums.DragProtocol), MonadIO m, IsDragContext a) => O.MethodInfo DragContextGetProtocolMethodInfo a signature where
    overloadedMethod = dragContextGetProtocol

#endif

-- method DragContext::get_selected_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "DragAction" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_get_selected_action" gdk_drag_context_get_selected_action :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO CUInt

-- | Determines the action chosen by the drag destination.
-- 
-- /Since: 2.22/
dragContextGetSelectedAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m [Gdk.Flags.DragAction]
    -- ^ __Returns:__ a t'GI.Gdk.Flags.DragAction' value
dragContextGetSelectedAction :: a -> m [DragAction]
dragContextGetSelectedAction a
context = IO [DragAction] -> m [DragAction]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DragAction] -> m [DragAction])
-> IO [DragAction] -> m [DragAction]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CUInt
result <- Ptr DragContext -> IO CUInt
gdk_drag_context_get_selected_action Ptr DragContext
context'
    let result' :: [DragAction]
result' = CUInt -> [DragAction]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    [DragAction] -> IO [DragAction]
forall (m :: * -> *) a. Monad m => a -> m a
return [DragAction]
result'

#if defined(ENABLE_OVERLOADING)
data DragContextGetSelectedActionMethodInfo
instance (signature ~ (m [Gdk.Flags.DragAction]), MonadIO m, IsDragContext a) => O.MethodInfo DragContextGetSelectedActionMethodInfo a signature where
    overloadedMethod = dragContextGetSelectedAction

#endif

-- method DragContext::get_source_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_get_source_window" gdk_drag_context_get_source_window :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO (Ptr Gdk.Window.Window)

-- | Returns the t'GI.Gdk.Objects.Window.Window' where the DND operation started.
-- 
-- /Since: 2.22/
dragContextGetSourceWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m Gdk.Window.Window
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Window.Window'
dragContextGetSourceWindow :: a -> m Window
dragContextGetSourceWindow a
context = IO Window -> m Window
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Window
result <- Ptr DragContext -> IO (Ptr Window)
gdk_drag_context_get_source_window Ptr DragContext
context'
    Text -> Ptr Window -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dragContextGetSourceWindow" Ptr Window
result
    Window
result' <- ((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
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result'

#if defined(ENABLE_OVERLOADING)
data DragContextGetSourceWindowMethodInfo
instance (signature ~ (m Gdk.Window.Window), MonadIO m, IsDragContext a) => O.MethodInfo DragContextGetSourceWindowMethodInfo a signature where
    overloadedMethod = dragContextGetSourceWindow

#endif

-- method DragContext::get_suggested_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "DragAction" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_get_suggested_action" gdk_drag_context_get_suggested_action :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO CUInt

-- | Determines the suggested drag action of the context.
-- 
-- /Since: 2.22/
dragContextGetSuggestedAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m [Gdk.Flags.DragAction]
    -- ^ __Returns:__ a t'GI.Gdk.Flags.DragAction' value
dragContextGetSuggestedAction :: a -> m [DragAction]
dragContextGetSuggestedAction a
context = IO [DragAction] -> m [DragAction]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DragAction] -> m [DragAction])
-> IO [DragAction] -> m [DragAction]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CUInt
result <- Ptr DragContext -> IO CUInt
gdk_drag_context_get_suggested_action Ptr DragContext
context'
    let result' :: [DragAction]
result' = CUInt -> [DragAction]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    [DragAction] -> IO [DragAction]
forall (m :: * -> *) a. Monad m => a -> m a
return [DragAction]
result'

#if defined(ENABLE_OVERLOADING)
data DragContextGetSuggestedActionMethodInfo
instance (signature ~ (m [Gdk.Flags.DragAction]), MonadIO m, IsDragContext a) => O.MethodInfo DragContextGetSuggestedActionMethodInfo a signature where
    overloadedMethod = dragContextGetSuggestedAction

#endif

-- method DragContext::list_targets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "Gdk" , name = "Atom" }))
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_list_targets" gdk_drag_context_list_targets :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    IO (Ptr (GList (Ptr Gdk.Atom.Atom)))

-- | Retrieves the list of targets of the context.
-- 
-- /Since: 2.22/
dragContextListTargets ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> m [Gdk.Atom.Atom]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of targets
dragContextListTargets :: a -> m [Atom]
dragContextListTargets a
context = IO [Atom] -> m [Atom]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Atom] -> m [Atom]) -> IO [Atom] -> m [Atom]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr (GList (Ptr Atom))
result <- Ptr DragContext -> IO (Ptr (GList (Ptr Atom)))
gdk_drag_context_list_targets Ptr DragContext
context'
    [Ptr Atom]
result' <- Ptr (GList (Ptr Atom)) -> IO [Ptr Atom]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Atom))
result
    [Atom]
result'' <- (Ptr Atom -> IO Atom) -> [Ptr Atom] -> IO [Atom]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Atom -> Atom) -> Ptr Atom -> IO Atom
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Atom -> Atom
Gdk.Atom.Atom) [Ptr Atom]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    [Atom] -> IO [Atom]
forall (m :: * -> *) a. Monad m => a -> m a
return [Atom]
result''

#if defined(ENABLE_OVERLOADING)
data DragContextListTargetsMethodInfo
instance (signature ~ (m [Gdk.Atom.Atom]), MonadIO m, IsDragContext a) => O.MethodInfo DragContextListTargetsMethodInfo a signature where
    overloadedMethod = dragContextListTargets

#endif

-- method DragContext::manage_dnd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ipc_window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Window to use for IPC messaging/events"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actions"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragAction" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the actions supported by the drag source"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_manage_dnd" gdk_drag_context_manage_dnd :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    Ptr Gdk.Window.Window ->                -- ipc_window : TInterface (Name {namespace = "Gdk", name = "Window"})
    CUInt ->                                -- actions : TInterface (Name {namespace = "Gdk", name = "DragAction"})
    IO CInt

-- | Requests the drag and drop operation to be managed by /@context@/.
-- When a drag and drop operation becomes managed, the t'GI.Gdk.Objects.DragContext.DragContext'
-- will internally handle all input and source-side t'GI.Gdk.Structs.EventDND.EventDND' events
-- as required by the windowing system.
-- 
-- Once the drag and drop operation is managed, the drag context will
-- emit the following signals:
-- 
-- * The [actionChanged]("GI.Gdk.Objects.DragContext#g:signal:actionChanged") signal whenever the final action
-- to be performed by the drag and drop operation changes.
-- * The [dropPerformed]("GI.Gdk.Objects.DragContext#g:signal:dropPerformed") signal after the user performs
-- the drag and drop gesture (typically by releasing the mouse button).
-- * The [dndFinished]("GI.Gdk.Objects.DragContext#g:signal:dndFinished") signal after the drag and drop
-- operation concludes (after all @/GdkSelection/@ transfers happen).
-- * The [cancel]("GI.Gdk.Objects.DragContext#g:signal:cancel") signal if the drag and drop operation is
-- finished but doesn\'t happen over an accepting destination, or is
-- cancelled through other means.
-- 
-- 
-- /Since: 3.20/
dragContextManageDnd ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a, Gdk.Window.IsWindow b) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> b
    -- ^ /@ipcWindow@/: Window to use for IPC messaging\/events
    -> [Gdk.Flags.DragAction]
    -- ^ /@actions@/: the actions supported by the drag source
    -> m Bool
    -- ^ __Returns:__ @/TRUE/@ if the drag and drop operation is managed.
dragContextManageDnd :: a -> b -> [DragAction] -> m Bool
dragContextManageDnd a
context b
ipcWindow [DragAction]
actions = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Window
ipcWindow' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
ipcWindow
    let actions' :: CUInt
actions' = [DragAction] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DragAction]
actions
    CInt
result <- Ptr DragContext -> Ptr Window -> CUInt -> IO CInt
gdk_drag_context_manage_dnd Ptr DragContext
context' Ptr Window
ipcWindow' CUInt
actions'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
ipcWindow
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DragContextManageDndMethodInfo
instance (signature ~ (b -> [Gdk.Flags.DragAction] -> m Bool), MonadIO m, IsDragContext a, Gdk.Window.IsWindow b) => O.MethodInfo DragContextManageDndMethodInfo a signature where
    overloadedMethod = dragContextManageDnd

#endif

-- method DragContext::set_device
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_set_device" gdk_drag_context_set_device :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    Ptr Gdk.Device.Device ->                -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO ()

-- | Associates a t'GI.Gdk.Objects.Device.Device' to /@context@/, so all Drag and Drop events
-- for /@context@/ are emitted as if they came from this device.
dragContextSetDevice ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a, Gdk.Device.IsDevice b) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> b
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m ()
dragContextSetDevice :: a -> b -> m ()
dragContextSetDevice a
context b
device = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Device
device' <- b -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
device
    Ptr DragContext -> Ptr Device -> IO ()
gdk_drag_context_set_device Ptr DragContext
context' Ptr Device
device'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
device
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DragContextSetDeviceMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDragContext a, Gdk.Device.IsDevice b) => O.MethodInfo DragContextSetDeviceMethodInfo a signature where
    overloadedMethod = dragContextSetDevice

#endif

-- method DragContext::set_hotspot
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DragContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDragContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "hot_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "x coordinate of the drag window hotspot"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "hot_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "y coordinate of the drag window hotspot"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_drag_context_set_hotspot" gdk_drag_context_set_hotspot :: 
    Ptr DragContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DragContext"})
    Int32 ->                                -- hot_x : TBasicType TInt
    Int32 ->                                -- hot_y : TBasicType TInt
    IO ()

-- | Sets the position of the drag window that will be kept
-- under the cursor hotspot. Initially, the hotspot is at the
-- top left corner of the drag window.
-- 
-- /Since: 3.20/
dragContextSetHotspot ::
    (B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.DragContext.DragContext'
    -> Int32
    -- ^ /@hotX@/: x coordinate of the drag window hotspot
    -> Int32
    -- ^ /@hotY@/: y coordinate of the drag window hotspot
    -> m ()
dragContextSetHotspot :: a -> Int32 -> Int32 -> m ()
dragContextSetHotspot a
context Int32
hotX Int32
hotY = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DragContext
context' <- a -> IO (Ptr DragContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr DragContext -> Int32 -> DragContextDropPerformedCallback
gdk_drag_context_set_hotspot Ptr DragContext
context' Int32
hotX Int32
hotY
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DragContextSetHotspotMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsDragContext a) => O.MethodInfo DragContextSetHotspotMethodInfo a signature where
    overloadedMethod = dragContextSetHotspot

#endif