{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.DragContext
(
DragContext(..) ,
IsDragContext ,
toDragContext ,
#if defined(ENABLE_OVERLOADING)
ResolveDragContextMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DragContextGetActionsMethodInfo ,
#endif
dragContextGetActions ,
#if defined(ENABLE_OVERLOADING)
DragContextGetDestWindowMethodInfo ,
#endif
dragContextGetDestWindow ,
#if defined(ENABLE_OVERLOADING)
DragContextGetDeviceMethodInfo ,
#endif
dragContextGetDevice ,
#if defined(ENABLE_OVERLOADING)
DragContextGetDragWindowMethodInfo ,
#endif
dragContextGetDragWindow ,
#if defined(ENABLE_OVERLOADING)
DragContextGetProtocolMethodInfo ,
#endif
dragContextGetProtocol ,
#if defined(ENABLE_OVERLOADING)
DragContextGetSelectedActionMethodInfo ,
#endif
dragContextGetSelectedAction ,
#if defined(ENABLE_OVERLOADING)
DragContextGetSourceWindowMethodInfo ,
#endif
dragContextGetSourceWindow ,
#if defined(ENABLE_OVERLOADING)
DragContextGetSuggestedActionMethodInfo ,
#endif
dragContextGetSuggestedAction ,
#if defined(ENABLE_OVERLOADING)
DragContextListTargetsMethodInfo ,
#endif
dragContextListTargets ,
#if defined(ENABLE_OVERLOADING)
DragContextManageDndMethodInfo ,
#endif
dragContextManageDnd ,
#if defined(ENABLE_OVERLOADING)
DragContextSetDeviceMethodInfo ,
#endif
dragContextSetDevice ,
#if defined(ENABLE_OVERLOADING)
DragContextSetHotspotMethodInfo ,
#endif
dragContextSetHotspot ,
DragContextActionChangedCallback ,
#if defined(ENABLE_OVERLOADING)
DragContextActionChangedSignalInfo ,
#endif
afterDragContextActionChanged ,
onDragContextActionChanged ,
DragContextCancelCallback ,
#if defined(ENABLE_OVERLOADING)
DragContextCancelSignalInfo ,
#endif
afterDragContextCancel ,
onDragContextCancel ,
DragContextDndFinishedCallback ,
#if defined(ENABLE_OVERLOADING)
DragContextDndFinishedSignalInfo ,
#endif
afterDragContextDndFinished ,
onDragContextDndFinished ,
DragContextDropPerformedCallback ,
#if defined(ENABLE_OVERLOADING)
DragContextDropPerformedSignalInfo ,
#endif
afterDragContextDropPerformed ,
onDragContextDropPerformed ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import 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
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
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]
toDragContext :: (MIO.MonadIO m, IsDragContext o) => o -> m DragContext
toDragContext :: forall (m :: * -> *) o.
(MonadIO m, IsDragContext o) =>
o -> m DragContext
toDragContext = IO DragContext -> m DragContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr DragContext -> DragContext
DragContext
instance B.GValue.IsGValue (Maybe DragContext) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_drag_context_get_type
gvalueSet_ :: Ptr GValue -> Maybe DragContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DragContext
P.Nothing = Ptr GValue -> Ptr DragContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DragContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr DragContext)
gvalueSet_ Ptr GValue
gv (P.Just DragContext
obj) = DragContext -> (Ptr DragContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DragContext
obj (Ptr GValue -> Ptr DragContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DragContext)
gvalueGet_ Ptr GValue
gv = do
Ptr DragContext
ptr <- Ptr GValue -> IO (Ptr DragContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DragContext)
if Ptr DragContext
ptr Ptr DragContext -> Ptr DragContext -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DragContext
forall a. Ptr a
FP.nullPtr
then DragContext -> Maybe DragContext
forall a. a -> Maybe a
P.Just (DragContext -> Maybe DragContext)
-> IO DragContext -> IO (Maybe DragContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
else Maybe DragContext -> IO (Maybe DragContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DragContext
forall a. Maybe a
P.Nothing
#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.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDragContextMethod t DragContext, O.OverloadedMethod info DragContext p, R.HasField t DragContext p) => R.HasField t DragContext p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDragContextMethod t DragContext, O.OverloadedMethodInfo info DragContext) => OL.IsLabel t (O.MethodProxy info DragContext) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type DragContextActionChangedCallback =
[Gdk.Flags.DragAction]
-> IO ()
type C_DragContextActionChangedCallback =
Ptr DragContext ->
CUInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DragContextActionChangedCallback :: C_DragContextActionChangedCallback -> IO (FunPtr C_DragContextActionChangedCallback)
wrap_DragContextActionChangedCallback ::
GObject a => (a -> DragContextActionChangedCallback) ->
C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback :: forall a.
GObject a =>
(a -> DragContextActionChangedCallback)
-> C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback a -> DragContextActionChangedCallback
gi'cb Ptr DragContext
gi'selfPtr 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
Ptr DragContext -> (DragContext -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr DragContext
gi'selfPtr ((DragContext -> IO ()) -> IO ())
-> (DragContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DragContext
gi'self -> a -> DragContextActionChangedCallback
gi'cb (DragContext -> a
Coerce.coerce DragContext
gi'self) [DragAction]
action'
onDragContextActionChanged :: (IsDragContext a, MonadIO m) => a -> ((?self :: a) => DragContextActionChangedCallback) -> m SignalHandlerId
onDragContextActionChanged :: forall a (m :: * -> *).
(IsDragContext a, MonadIO m) =>
a
-> ((?self::a) => DragContextActionChangedCallback)
-> m SignalHandlerId
onDragContextActionChanged a
obj (?self::a) => 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 wrapped :: a -> DragContextActionChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DragContextActionChangedCallback
DragContextActionChangedCallback
cb
let wrapped' :: C_DragContextActionChangedCallback
wrapped' = (a -> DragContextActionChangedCallback)
-> C_DragContextActionChangedCallback
forall a.
GObject a =>
(a -> DragContextActionChangedCallback)
-> C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback a -> DragContextActionChangedCallback
wrapped
FunPtr C_DragContextActionChangedCallback
wrapped'' <- C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextActionChangedCallback C_DragContextActionChangedCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDragContextActionChanged :: (IsDragContext a, MonadIO m) => a -> ((?self :: a) => DragContextActionChangedCallback) -> m SignalHandlerId
afterDragContextActionChanged :: forall a (m :: * -> *).
(IsDragContext a, MonadIO m) =>
a
-> ((?self::a) => DragContextActionChangedCallback)
-> m SignalHandlerId
afterDragContextActionChanged a
obj (?self::a) => 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 wrapped :: a -> DragContextActionChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DragContextActionChangedCallback
DragContextActionChangedCallback
cb
let wrapped' :: C_DragContextActionChangedCallback
wrapped' = (a -> DragContextActionChangedCallback)
-> C_DragContextActionChangedCallback
forall a.
GObject a =>
(a -> DragContextActionChangedCallback)
-> C_DragContextActionChangedCallback
wrap_DragContextActionChangedCallback a -> DragContextActionChangedCallback
wrapped
FunPtr C_DragContextActionChangedCallback
wrapped'' <- C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextActionChangedCallback C_DragContextActionChangedCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext::action-changed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#g:signal:actionChanged"})
#endif
type DragContextCancelCallback =
Gdk.Enums.DragCancelReason
-> IO ()
type C_DragContextCancelCallback =
Ptr DragContext ->
CUInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DragContextCancelCallback :: C_DragContextCancelCallback -> IO (FunPtr C_DragContextCancelCallback)
wrap_DragContextCancelCallback ::
GObject a => (a -> DragContextCancelCallback) ->
C_DragContextCancelCallback
wrap_DragContextCancelCallback :: forall a.
GObject a =>
(a -> DragContextCancelCallback)
-> C_DragContextActionChangedCallback
wrap_DragContextCancelCallback a -> DragContextCancelCallback
gi'cb Ptr DragContext
gi'selfPtr 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
Ptr DragContext -> (DragContext -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr DragContext
gi'selfPtr ((DragContext -> IO ()) -> IO ())
-> (DragContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DragContext
gi'self -> a -> DragContextCancelCallback
gi'cb (DragContext -> a
Coerce.coerce DragContext
gi'self) DragCancelReason
reason'
onDragContextCancel :: (IsDragContext a, MonadIO m) => a -> ((?self :: a) => DragContextCancelCallback) -> m SignalHandlerId
onDragContextCancel :: forall a (m :: * -> *).
(IsDragContext a, MonadIO m) =>
a -> ((?self::a) => DragContextCancelCallback) -> m SignalHandlerId
onDragContextCancel a
obj (?self::a) => 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 wrapped :: a -> DragContextCancelCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DragContextCancelCallback
DragContextCancelCallback
cb
let wrapped' :: C_DragContextActionChangedCallback
wrapped' = (a -> DragContextCancelCallback)
-> C_DragContextActionChangedCallback
forall a.
GObject a =>
(a -> DragContextCancelCallback)
-> C_DragContextActionChangedCallback
wrap_DragContextCancelCallback a -> DragContextCancelCallback
wrapped
FunPtr C_DragContextActionChangedCallback
wrapped'' <- C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextCancelCallback C_DragContextActionChangedCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDragContextCancel :: (IsDragContext a, MonadIO m) => a -> ((?self :: a) => DragContextCancelCallback) -> m SignalHandlerId
afterDragContextCancel :: forall a (m :: * -> *).
(IsDragContext a, MonadIO m) =>
a -> ((?self::a) => DragContextCancelCallback) -> m SignalHandlerId
afterDragContextCancel a
obj (?self::a) => 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 wrapped :: a -> DragContextCancelCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DragContextCancelCallback
DragContextCancelCallback
cb
let wrapped' :: C_DragContextActionChangedCallback
wrapped' = (a -> DragContextCancelCallback)
-> C_DragContextActionChangedCallback
forall a.
GObject a =>
(a -> DragContextCancelCallback)
-> C_DragContextActionChangedCallback
wrap_DragContextCancelCallback a -> DragContextCancelCallback
wrapped
FunPtr C_DragContextActionChangedCallback
wrapped'' <- C_DragContextActionChangedCallback
-> IO (FunPtr C_DragContextActionChangedCallback)
mk_DragContextCancelCallback C_DragContextActionChangedCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext::cancel"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#g:signal:cancel"})
#endif
type DragContextDndFinishedCallback =
IO ()
type C_DragContextDndFinishedCallback =
Ptr DragContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DragContextDndFinishedCallback :: C_DragContextDndFinishedCallback -> IO (FunPtr C_DragContextDndFinishedCallback)
wrap_DragContextDndFinishedCallback ::
GObject a => (a -> DragContextDndFinishedCallback) ->
C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback a -> IO ()
gi'cb Ptr DragContext
gi'selfPtr Ptr ()
_ = do
Ptr DragContext -> (DragContext -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr DragContext
gi'selfPtr ((DragContext -> IO ()) -> IO ())
-> (DragContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DragContext
gi'self -> a -> IO ()
gi'cb (DragContext -> a
Coerce.coerce DragContext
gi'self)
onDragContextDndFinished :: (IsDragContext a, MonadIO m) => a -> ((?self :: a) => DragContextDndFinishedCallback) -> m SignalHandlerId
onDragContextDndFinished :: forall a (m :: * -> *).
(IsDragContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDragContextDndFinished a
obj (?self::a) => 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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DragContextDndFinishedCallback
wrapped' = (a -> IO ()) -> C_DragContextDndFinishedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback a -> IO ()
wrapped
FunPtr C_DragContextDndFinishedCallback
wrapped'' <- C_DragContextDndFinishedCallback
-> IO (FunPtr C_DragContextDndFinishedCallback)
mk_DragContextDndFinishedCallback C_DragContextDndFinishedCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDragContextDndFinished :: (IsDragContext a, MonadIO m) => a -> ((?self :: a) => DragContextDndFinishedCallback) -> m SignalHandlerId
afterDragContextDndFinished :: forall a (m :: * -> *).
(IsDragContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDragContextDndFinished a
obj (?self::a) => 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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DragContextDndFinishedCallback
wrapped' = (a -> IO ()) -> C_DragContextDndFinishedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DragContextDndFinishedCallback
wrap_DragContextDndFinishedCallback a -> IO ()
wrapped
FunPtr C_DragContextDndFinishedCallback
wrapped'' <- C_DragContextDndFinishedCallback
-> IO (FunPtr C_DragContextDndFinishedCallback)
mk_DragContextDndFinishedCallback C_DragContextDndFinishedCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext::dnd-finished"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#g:signal:dndFinished"})
#endif
type DragContextDropPerformedCallback =
Int32
-> IO ()
type C_DragContextDropPerformedCallback =
Ptr DragContext ->
Int32 ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DragContextDropPerformedCallback :: C_DragContextDropPerformedCallback -> IO (FunPtr C_DragContextDropPerformedCallback)
wrap_DragContextDropPerformedCallback ::
GObject a => (a -> DragContextDropPerformedCallback) ->
C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback :: forall a.
GObject a =>
(a -> DragContextDropPerformedCallback)
-> C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback a -> DragContextDropPerformedCallback
gi'cb Ptr DragContext
gi'selfPtr Int32
time Ptr ()
_ = do
Ptr DragContext -> (DragContext -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr DragContext
gi'selfPtr ((DragContext -> IO ()) -> IO ())
-> (DragContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DragContext
gi'self -> a -> DragContextDropPerformedCallback
gi'cb (DragContext -> a
Coerce.coerce DragContext
gi'self) Int32
time
onDragContextDropPerformed :: (IsDragContext a, MonadIO m) => a -> ((?self :: a) => DragContextDropPerformedCallback) -> m SignalHandlerId
onDragContextDropPerformed :: forall a (m :: * -> *).
(IsDragContext a, MonadIO m) =>
a
-> ((?self::a) => DragContextDropPerformedCallback)
-> m SignalHandlerId
onDragContextDropPerformed a
obj (?self::a) => 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 wrapped :: a -> DragContextDropPerformedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DragContextDropPerformedCallback
DragContextDropPerformedCallback
cb
let wrapped' :: C_DragContextDropPerformedCallback
wrapped' = (a -> DragContextDropPerformedCallback)
-> C_DragContextDropPerformedCallback
forall a.
GObject a =>
(a -> DragContextDropPerformedCallback)
-> C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback a -> DragContextDropPerformedCallback
wrapped
FunPtr C_DragContextDropPerformedCallback
wrapped'' <- C_DragContextDropPerformedCallback
-> IO (FunPtr C_DragContextDropPerformedCallback)
mk_DragContextDropPerformedCallback C_DragContextDropPerformedCallback
wrapped'
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
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDragContextDropPerformed :: (IsDragContext a, MonadIO m) => a -> ((?self :: a) => DragContextDropPerformedCallback) -> m SignalHandlerId
afterDragContextDropPerformed :: forall a (m :: * -> *).
(IsDragContext a, MonadIO m) =>
a
-> ((?self::a) => DragContextDropPerformedCallback)
-> m SignalHandlerId
afterDragContextDropPerformed a
obj (?self::a) => 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 wrapped :: a -> DragContextDropPerformedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DragContextDropPerformedCallback
DragContextDropPerformedCallback
cb
let wrapped' :: C_DragContextDropPerformedCallback
wrapped' = (a -> DragContextDropPerformedCallback)
-> C_DragContextDropPerformedCallback
forall a.
GObject a =>
(a -> DragContextDropPerformedCallback)
-> C_DragContextDropPerformedCallback
wrap_DragContextDropPerformedCallback a -> DragContextDropPerformedCallback
wrapped
FunPtr C_DragContextDropPerformedCallback
wrapped'' <- C_DragContextDropPerformedCallback
-> IO (FunPtr C_DragContextDropPerformedCallback)
mk_DragContextDropPerformedCallback C_DragContextDropPerformedCallback
wrapped'
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
wrapped'' 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext::drop-performed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#g:signal:dropPerformed"})
#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
foreign import ccall "gdk_drag_context_get_actions" gdk_drag_context_get_actions ::
Ptr DragContext ->
IO CUInt
dragContextGetActions ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m [Gdk.Flags.DragAction]
dragContextGetActions :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextGetActionsMethodInfo a signature where
overloadedMethod = dragContextGetActions
instance O.OverloadedMethodInfo DragContextGetActionsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextGetActions",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextGetActions"
})
#endif
foreign import ccall "gdk_drag_context_get_dest_window" gdk_drag_context_get_dest_window ::
Ptr DragContext ->
IO (Ptr Gdk.Window.Window)
dragContextGetDestWindow ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m Gdk.Window.Window
dragContextGetDestWindow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextGetDestWindowMethodInfo a signature where
overloadedMethod = dragContextGetDestWindow
instance O.OverloadedMethodInfo DragContextGetDestWindowMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextGetDestWindow",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextGetDestWindow"
})
#endif
foreign import ccall "gdk_drag_context_get_device" gdk_drag_context_get_device ::
Ptr DragContext ->
IO (Ptr Gdk.Device.Device)
dragContextGetDevice ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m Gdk.Device.Device
dragContextGetDevice :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextGetDeviceMethodInfo a signature where
overloadedMethod = dragContextGetDevice
instance O.OverloadedMethodInfo DragContextGetDeviceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextGetDevice",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextGetDevice"
})
#endif
foreign import ccall "gdk_drag_context_get_drag_window" gdk_drag_context_get_drag_window ::
Ptr DragContext ->
IO (Ptr Gdk.Window.Window)
dragContextGetDragWindow ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m (Maybe Gdk.Window.Window)
dragContextGetDragWindow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextGetDragWindowMethodInfo a signature where
overloadedMethod = dragContextGetDragWindow
instance O.OverloadedMethodInfo DragContextGetDragWindowMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextGetDragWindow",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextGetDragWindow"
})
#endif
foreign import ccall "gdk_drag_context_get_protocol" gdk_drag_context_get_protocol ::
Ptr DragContext ->
IO CUInt
dragContextGetProtocol ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m Gdk.Enums.DragProtocol
dragContextGetProtocol :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextGetProtocolMethodInfo a signature where
overloadedMethod = dragContextGetProtocol
instance O.OverloadedMethodInfo DragContextGetProtocolMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextGetProtocol",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextGetProtocol"
})
#endif
foreign import ccall "gdk_drag_context_get_selected_action" gdk_drag_context_get_selected_action ::
Ptr DragContext ->
IO CUInt
dragContextGetSelectedAction ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m [Gdk.Flags.DragAction]
dragContextGetSelectedAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextGetSelectedActionMethodInfo a signature where
overloadedMethod = dragContextGetSelectedAction
instance O.OverloadedMethodInfo DragContextGetSelectedActionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextGetSelectedAction",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextGetSelectedAction"
})
#endif
foreign import ccall "gdk_drag_context_get_source_window" gdk_drag_context_get_source_window ::
Ptr DragContext ->
IO (Ptr Gdk.Window.Window)
dragContextGetSourceWindow ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m Gdk.Window.Window
dragContextGetSourceWindow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextGetSourceWindowMethodInfo a signature where
overloadedMethod = dragContextGetSourceWindow
instance O.OverloadedMethodInfo DragContextGetSourceWindowMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextGetSourceWindow",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextGetSourceWindow"
})
#endif
foreign import ccall "gdk_drag_context_get_suggested_action" gdk_drag_context_get_suggested_action ::
Ptr DragContext ->
IO CUInt
dragContextGetSuggestedAction ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m [Gdk.Flags.DragAction]
dragContextGetSuggestedAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextGetSuggestedActionMethodInfo a signature where
overloadedMethod = dragContextGetSuggestedAction
instance O.OverloadedMethodInfo DragContextGetSuggestedActionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextGetSuggestedAction",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextGetSuggestedAction"
})
#endif
foreign import ccall "gdk_drag_context_list_targets" gdk_drag_context_list_targets ::
Ptr DragContext ->
IO (Ptr (GList (Ptr Gdk.Atom.Atom)))
dragContextListTargets ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> m [Gdk.Atom.Atom]
dragContextListTargets :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextListTargetsMethodInfo a signature where
overloadedMethod = dragContextListTargets
instance O.OverloadedMethodInfo DragContextListTargetsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextListTargets",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextListTargets"
})
#endif
foreign import ccall "gdk_drag_context_manage_dnd" gdk_drag_context_manage_dnd ::
Ptr DragContext ->
Ptr Gdk.Window.Window ->
CUInt ->
IO CInt
dragContextManageDnd ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a, Gdk.Window.IsWindow b) =>
a
-> b
-> [Gdk.Flags.DragAction]
-> m Bool
dragContextManageDnd :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDragContext a, IsWindow b) =>
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.OverloadedMethod DragContextManageDndMethodInfo a signature where
overloadedMethod = dragContextManageDnd
instance O.OverloadedMethodInfo DragContextManageDndMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextManageDnd",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextManageDnd"
})
#endif
foreign import ccall "gdk_drag_context_set_device" gdk_drag_context_set_device ::
Ptr DragContext ->
Ptr Gdk.Device.Device ->
IO ()
dragContextSetDevice ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a, Gdk.Device.IsDevice b) =>
a
-> b
-> m ()
dragContextSetDevice :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDragContext a, IsDevice b) =>
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.OverloadedMethod DragContextSetDeviceMethodInfo a signature where
overloadedMethod = dragContextSetDevice
instance O.OverloadedMethodInfo DragContextSetDeviceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextSetDevice",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextSetDevice"
})
#endif
foreign import ccall "gdk_drag_context_set_hotspot" gdk_drag_context_set_hotspot ::
Ptr DragContext ->
Int32 ->
Int32 ->
IO ()
dragContextSetHotspot ::
(B.CallStack.HasCallStack, MonadIO m, IsDragContext a) =>
a
-> Int32
-> Int32
-> m ()
dragContextSetHotspot :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDragContext a) =>
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.OverloadedMethod DragContextSetHotspotMethodInfo a signature where
overloadedMethod = dragContextSetHotspot
instance O.OverloadedMethodInfo DragContextSetHotspotMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DragContext.dragContextSetHotspot",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-DragContext.html#v:dragContextSetHotspot"
})
#endif