{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- 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.GdkX11.Objects.X11DragContext
    ( 

-- * Exported types
    X11DragContext(..)                      ,
    IsX11DragContext                        ,
    toX11DragContext                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [listTargets]("GI.Gdk.Objects.DragContext#g:method:listTargets"), [manageDnd]("GI.Gdk.Objects.DragContext#g:method:manageDnd"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getActions]("GI.Gdk.Objects.DragContext#g:method:getActions"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDestWindow]("GI.Gdk.Objects.DragContext#g:method:getDestWindow"), [getDevice]("GI.Gdk.Objects.DragContext#g:method:getDevice"), [getDragWindow]("GI.Gdk.Objects.DragContext#g:method:getDragWindow"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getProtocol]("GI.Gdk.Objects.DragContext#g:method:getProtocol"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSelectedAction]("GI.Gdk.Objects.DragContext#g:method:getSelectedAction"), [getSourceWindow]("GI.Gdk.Objects.DragContext#g:method:getSourceWindow"), [getSuggestedAction]("GI.Gdk.Objects.DragContext#g:method:getSuggestedAction").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDevice]("GI.Gdk.Objects.DragContext#g:method:setDevice"), [setHotspot]("GI.Gdk.Objects.DragContext#g:method:setHotspot"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveX11DragContextMethod             ,
#endif



    ) 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.GHashTable as B.GHT
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 qualified GI.Gdk.Objects.DragContext as Gdk.DragContext

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

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

foreign import ccall "gdk_x11_drag_context_get_type"
    c_gdk_x11_drag_context_get_type :: IO B.Types.GType

instance B.Types.TypedObject X11DragContext where
    glibType :: IO GType
glibType = IO GType
c_gdk_x11_drag_context_get_type

instance B.Types.GObject X11DragContext

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

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

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

-- | Convert 'X11DragContext' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe X11DragContext) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_x11_drag_context_get_type
    gvalueSet_ :: Ptr GValue -> Maybe X11DragContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe X11DragContext
P.Nothing = Ptr GValue -> Ptr X11DragContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr X11DragContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr X11DragContext)
    gvalueSet_ Ptr GValue
gv (P.Just X11DragContext
obj) = X11DragContext -> (Ptr X11DragContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr X11DragContext
obj (Ptr GValue -> Ptr X11DragContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe X11DragContext)
gvalueGet_ Ptr GValue
gv = do
        Ptr X11DragContext
ptr <- Ptr GValue -> IO (Ptr X11DragContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr X11DragContext)
        if Ptr X11DragContext
ptr Ptr X11DragContext -> Ptr X11DragContext -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr X11DragContext
forall a. Ptr a
FP.nullPtr
        then X11DragContext -> Maybe X11DragContext
forall a. a -> Maybe a
P.Just (X11DragContext -> Maybe X11DragContext)
-> IO X11DragContext -> IO (Maybe X11DragContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr X11DragContext -> X11DragContext)
-> Ptr X11DragContext -> IO X11DragContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr X11DragContext -> X11DragContext
X11DragContext Ptr X11DragContext
ptr
        else Maybe X11DragContext -> IO (Maybe X11DragContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe X11DragContext
forall a. Maybe a
P.Nothing
        
    

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

instance (info ~ ResolveX11DragContextMethod t X11DragContext, O.OverloadedMethod info X11DragContext p) => OL.IsLabel t (X11DragContext -> 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 ~ ResolveX11DragContextMethod t X11DragContext, O.OverloadedMethod info X11DragContext p, R.HasField t X11DragContext p) => R.HasField t X11DragContext p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveX11DragContextMethod t X11DragContext, O.OverloadedMethodInfo info X11DragContext) => OL.IsLabel t (O.MethodProxy info X11DragContext) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif