{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.TreeDragSource
(
TreeDragSource(..) ,
noTreeDragSource ,
IsTreeDragSource ,
#if defined(ENABLE_OVERLOADING)
ResolveTreeDragSourceMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TreeDragSourceDragDataDeleteMethodInfo ,
#endif
treeDragSourceDragDataDelete ,
#if defined(ENABLE_OVERLOADING)
TreeDragSourceDragDataGetMethodInfo ,
#endif
treeDragSourceDragDataGet ,
#if defined(ENABLE_OVERLOADING)
TreeDragSourceRowDraggableMethodInfo ,
#endif
treeDragSourceRowDraggable ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import {-# SOURCE #-} qualified GI.Gtk.Structs.SelectionData as Gtk.SelectionData
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreePath as Gtk.TreePath
newtype TreeDragSource = TreeDragSource (ManagedPtr TreeDragSource)
deriving (TreeDragSource -> TreeDragSource -> Bool
(TreeDragSource -> TreeDragSource -> Bool)
-> (TreeDragSource -> TreeDragSource -> Bool) -> Eq TreeDragSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TreeDragSource -> TreeDragSource -> Bool
$c/= :: TreeDragSource -> TreeDragSource -> Bool
== :: TreeDragSource -> TreeDragSource -> Bool
$c== :: TreeDragSource -> TreeDragSource -> Bool
Eq)
noTreeDragSource :: Maybe TreeDragSource
noTreeDragSource :: Maybe TreeDragSource
noTreeDragSource = Maybe TreeDragSource
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TreeDragSource = TreeDragSourceSignalList
type TreeDragSourceSignalList = ('[ ] :: [(Symbol, *)])
#endif
class (ManagedPtrNewtype o, O.IsDescendantOf TreeDragSource o) => IsTreeDragSource o
instance (ManagedPtrNewtype o, O.IsDescendantOf TreeDragSource o) => IsTreeDragSource o
instance WrappedPtr TreeDragSource where
wrappedPtrCalloc :: IO (Ptr TreeDragSource)
wrappedPtrCalloc = Ptr TreeDragSource -> IO (Ptr TreeDragSource)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeDragSource
forall a. Ptr a
nullPtr
wrappedPtrCopy :: TreeDragSource -> IO TreeDragSource
wrappedPtrCopy = TreeDragSource -> IO TreeDragSource
forall (m :: * -> *) a. Monad m => a -> m a
return
wrappedPtrFree :: Maybe (GDestroyNotify TreeDragSource)
wrappedPtrFree = Maybe (GDestroyNotify TreeDragSource)
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveTreeDragSourceMethod (t :: Symbol) (o :: *) :: * where
ResolveTreeDragSourceMethod "dragDataDelete" o = TreeDragSourceDragDataDeleteMethodInfo
ResolveTreeDragSourceMethod "dragDataGet" o = TreeDragSourceDragDataGetMethodInfo
ResolveTreeDragSourceMethod "rowDraggable" o = TreeDragSourceRowDraggableMethodInfo
ResolveTreeDragSourceMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTreeDragSourceMethod t TreeDragSource, O.MethodInfo info TreeDragSource p) => OL.IsLabel t (TreeDragSource -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "gtk_tree_drag_source_drag_data_delete" gtk_tree_drag_source_drag_data_delete ::
Ptr TreeDragSource ->
Ptr Gtk.TreePath.TreePath ->
IO CInt
treeDragSourceDragDataDelete ::
(B.CallStack.HasCallStack, MonadIO m, IsTreeDragSource a) =>
a
-> Gtk.TreePath.TreePath
-> m Bool
treeDragSourceDragDataDelete :: a -> TreePath -> m Bool
treeDragSourceDragDataDelete dragSource :: a
dragSource path :: TreePath
path = 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 TreeDragSource
dragSource' <- a -> IO (Ptr TreeDragSource)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dragSource
Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
CInt
result <- Ptr TreeDragSource -> Ptr TreePath -> IO CInt
gtk_tree_drag_source_drag_data_delete Ptr TreeDragSource
dragSource' Ptr TreePath
path'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dragSource
TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TreeDragSourceDragDataDeleteMethodInfo
instance (signature ~ (Gtk.TreePath.TreePath -> m Bool), MonadIO m, IsTreeDragSource a) => O.MethodInfo TreeDragSourceDragDataDeleteMethodInfo a signature where
overloadedMethod = treeDragSourceDragDataDelete
#endif
foreign import ccall "gtk_tree_drag_source_drag_data_get" gtk_tree_drag_source_drag_data_get ::
Ptr TreeDragSource ->
Ptr Gtk.TreePath.TreePath ->
Ptr Gtk.SelectionData.SelectionData ->
IO CInt
treeDragSourceDragDataGet ::
(B.CallStack.HasCallStack, MonadIO m, IsTreeDragSource a) =>
a
-> Gtk.TreePath.TreePath
-> Gtk.SelectionData.SelectionData
-> m Bool
treeDragSourceDragDataGet :: a -> TreePath -> SelectionData -> m Bool
treeDragSourceDragDataGet dragSource :: a
dragSource path :: TreePath
path selectionData :: SelectionData
selectionData = 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 TreeDragSource
dragSource' <- a -> IO (Ptr TreeDragSource)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dragSource
Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
CInt
result <- Ptr TreeDragSource -> Ptr TreePath -> Ptr SelectionData -> IO CInt
gtk_tree_drag_source_drag_data_get Ptr TreeDragSource
dragSource' Ptr TreePath
path' Ptr SelectionData
selectionData'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dragSource
TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TreeDragSourceDragDataGetMethodInfo
instance (signature ~ (Gtk.TreePath.TreePath -> Gtk.SelectionData.SelectionData -> m Bool), MonadIO m, IsTreeDragSource a) => O.MethodInfo TreeDragSourceDragDataGetMethodInfo a signature where
overloadedMethod = treeDragSourceDragDataGet
#endif
foreign import ccall "gtk_tree_drag_source_row_draggable" gtk_tree_drag_source_row_draggable ::
Ptr TreeDragSource ->
Ptr Gtk.TreePath.TreePath ->
IO CInt
treeDragSourceRowDraggable ::
(B.CallStack.HasCallStack, MonadIO m, IsTreeDragSource a) =>
a
-> Gtk.TreePath.TreePath
-> m Bool
treeDragSourceRowDraggable :: a -> TreePath -> m Bool
treeDragSourceRowDraggable dragSource :: a
dragSource path :: TreePath
path = 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 TreeDragSource
dragSource' <- a -> IO (Ptr TreeDragSource)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
dragSource
Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
CInt
result <- Ptr TreeDragSource -> Ptr TreePath -> IO CInt
gtk_tree_drag_source_row_draggable Ptr TreeDragSource
dragSource' Ptr TreePath
path'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
dragSource
TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TreeDragSourceRowDraggableMethodInfo
instance (signature ~ (Gtk.TreePath.TreePath -> m Bool), MonadIO m, IsTreeDragSource a) => O.MethodInfo TreeDragSourceRowDraggableMethodInfo a signature where
overloadedMethod = treeDragSourceRowDraggable
#endif