{-# 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.Dazzle.Objects.DockTransientGrab
    ( 

-- * Exported types
    DockTransientGrab(..)                   ,
    IsDockTransientGrab                     ,
    toDockTransientGrab                     ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [acquire]("GI.Dazzle.Objects.DockTransientGrab#g:method:acquire"), [addItem]("GI.Dazzle.Objects.DockTransientGrab#g:method:addItem"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [cancel]("GI.Dazzle.Objects.DockTransientGrab#g:method:cancel"), [contains]("GI.Dazzle.Objects.DockTransientGrab#g:method:contains"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isDescendant]("GI.Dazzle.Objects.DockTransientGrab#g:method:isDescendant"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [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"), [release]("GI.Dazzle.Objects.DockTransientGrab#g:method:release"), [removeItem]("GI.Dazzle.Objects.DockTransientGrab#g:method:removeItem"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealCommonAncestors]("GI.Dazzle.Objects.DockTransientGrab#g:method:stealCommonAncestors"), [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
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTimeout]("GI.Dazzle.Objects.DockTransientGrab#g:method:getTimeout").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTimeout]("GI.Dazzle.Objects.DockTransientGrab#g:method:setTimeout").

#if defined(ENABLE_OVERLOADING)
    ResolveDockTransientGrabMethod          ,
#endif

-- ** acquire #method:acquire#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabAcquireMethodInfo      ,
#endif
    dockTransientGrabAcquire                ,


-- ** addItem #method:addItem#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabAddItemMethodInfo      ,
#endif
    dockTransientGrabAddItem                ,


-- ** cancel #method:cancel#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabCancelMethodInfo       ,
#endif
    dockTransientGrabCancel                 ,


-- ** contains #method:contains#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabContainsMethodInfo     ,
#endif
    dockTransientGrabContains               ,


-- ** getTimeout #method:getTimeout#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabGetTimeoutMethodInfo   ,
#endif
    dockTransientGrabGetTimeout             ,


-- ** isDescendant #method:isDescendant#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabIsDescendantMethodInfo ,
#endif
    dockTransientGrabIsDescendant           ,


-- ** new #method:new#

    dockTransientGrabNew                    ,


-- ** release #method:release#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabReleaseMethodInfo      ,
#endif
    dockTransientGrabRelease                ,


-- ** removeItem #method:removeItem#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabRemoveItemMethodInfo   ,
#endif
    dockTransientGrabRemoveItem             ,


-- ** setTimeout #method:setTimeout#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabSetTimeoutMethodInfo   ,
#endif
    dockTransientGrabSetTimeout             ,


-- ** stealCommonAncestors #method:stealCommonAncestors#

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabStealCommonAncestorsMethodInfo,
#endif
    dockTransientGrabStealCommonAncestors   ,




 -- * Properties


-- ** timeout #attr:timeout#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DockTransientGrabTimeoutPropertyInfo    ,
#endif
    constructDockTransientGrabTimeout       ,
#if defined(ENABLE_OVERLOADING)
    dockTransientGrabTimeout                ,
#endif
    getDockTransientGrabTimeout             ,
    setDockTransientGrabTimeout             ,




    ) 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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.Dock as Dazzle.Dock
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.DockItem as Dazzle.DockItem
import {-# SOURCE #-} qualified GI.Dazzle.Objects.DockManager as Dazzle.DockManager
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gtk.Enums as Gtk.Enums
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Widget as Gtk.Widget

#else
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.DockItem as Dazzle.DockItem
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Objects.Widget as Gtk.Widget

#endif

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

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

foreign import ccall "dzl_dock_transient_grab_get_type"
    c_dzl_dock_transient_grab_get_type :: IO B.Types.GType

instance B.Types.TypedObject DockTransientGrab where
    glibType :: IO GType
glibType = IO GType
c_dzl_dock_transient_grab_get_type

instance B.Types.GObject DockTransientGrab

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

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

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

-- | Convert 'DockTransientGrab' 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 DockTransientGrab) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_dock_transient_grab_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DockTransientGrab -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DockTransientGrab
P.Nothing = Ptr GValue -> Ptr DockTransientGrab -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DockTransientGrab
forall a. Ptr a
FP.nullPtr :: FP.Ptr DockTransientGrab)
    gvalueSet_ Ptr GValue
gv (P.Just DockTransientGrab
obj) = DockTransientGrab -> (Ptr DockTransientGrab -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DockTransientGrab
obj (Ptr GValue -> Ptr DockTransientGrab -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DockTransientGrab)
gvalueGet_ Ptr GValue
gv = do
        Ptr DockTransientGrab
ptr <- Ptr GValue -> IO (Ptr DockTransientGrab)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DockTransientGrab)
        if Ptr DockTransientGrab
ptr Ptr DockTransientGrab -> Ptr DockTransientGrab -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DockTransientGrab
forall a. Ptr a
FP.nullPtr
        then DockTransientGrab -> Maybe DockTransientGrab
forall a. a -> Maybe a
P.Just (DockTransientGrab -> Maybe DockTransientGrab)
-> IO DockTransientGrab -> IO (Maybe DockTransientGrab)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DockTransientGrab -> DockTransientGrab)
-> Ptr DockTransientGrab -> IO DockTransientGrab
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DockTransientGrab -> DockTransientGrab
DockTransientGrab Ptr DockTransientGrab
ptr
        else Maybe DockTransientGrab -> IO (Maybe DockTransientGrab)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DockTransientGrab
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDockTransientGrabMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDockTransientGrabMethod "acquire" o = DockTransientGrabAcquireMethodInfo
    ResolveDockTransientGrabMethod "addItem" o = DockTransientGrabAddItemMethodInfo
    ResolveDockTransientGrabMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDockTransientGrabMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDockTransientGrabMethod "cancel" o = DockTransientGrabCancelMethodInfo
    ResolveDockTransientGrabMethod "contains" o = DockTransientGrabContainsMethodInfo
    ResolveDockTransientGrabMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDockTransientGrabMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDockTransientGrabMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDockTransientGrabMethod "isDescendant" o = DockTransientGrabIsDescendantMethodInfo
    ResolveDockTransientGrabMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDockTransientGrabMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDockTransientGrabMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDockTransientGrabMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDockTransientGrabMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDockTransientGrabMethod "release" o = DockTransientGrabReleaseMethodInfo
    ResolveDockTransientGrabMethod "removeItem" o = DockTransientGrabRemoveItemMethodInfo
    ResolveDockTransientGrabMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDockTransientGrabMethod "stealCommonAncestors" o = DockTransientGrabStealCommonAncestorsMethodInfo
    ResolveDockTransientGrabMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDockTransientGrabMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDockTransientGrabMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDockTransientGrabMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDockTransientGrabMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDockTransientGrabMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDockTransientGrabMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDockTransientGrabMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDockTransientGrabMethod "getTimeout" o = DockTransientGrabGetTimeoutMethodInfo
    ResolveDockTransientGrabMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDockTransientGrabMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDockTransientGrabMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDockTransientGrabMethod "setTimeout" o = DockTransientGrabSetTimeoutMethodInfo
    ResolveDockTransientGrabMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "timeout"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@timeout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dockTransientGrab #timeout
-- @
getDockTransientGrabTimeout :: (MonadIO m, IsDockTransientGrab o) => o -> m Word32
getDockTransientGrabTimeout :: forall (m :: * -> *) o.
(MonadIO m, IsDockTransientGrab o) =>
o -> m Word32
getDockTransientGrabTimeout o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"timeout"

-- | Set the value of the “@timeout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dockTransientGrab [ #timeout 'Data.GI.Base.Attributes.:=' value ]
-- @
setDockTransientGrabTimeout :: (MonadIO m, IsDockTransientGrab o) => o -> Word32 -> m ()
setDockTransientGrabTimeout :: forall (m :: * -> *) o.
(MonadIO m, IsDockTransientGrab o) =>
o -> Word32 -> m ()
setDockTransientGrabTimeout o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"timeout" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@timeout@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDockTransientGrabTimeout :: (IsDockTransientGrab o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDockTransientGrabTimeout :: forall o (m :: * -> *).
(IsDockTransientGrab o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructDockTransientGrabTimeout Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"timeout" Word32
val

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabTimeoutPropertyInfo
instance AttrInfo DockTransientGrabTimeoutPropertyInfo where
    type AttrAllowedOps DockTransientGrabTimeoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DockTransientGrabTimeoutPropertyInfo = IsDockTransientGrab
    type AttrSetTypeConstraint DockTransientGrabTimeoutPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint DockTransientGrabTimeoutPropertyInfo = (~) Word32
    type AttrTransferType DockTransientGrabTimeoutPropertyInfo = Word32
    type AttrGetType DockTransientGrabTimeoutPropertyInfo = Word32
    type AttrLabel DockTransientGrabTimeoutPropertyInfo = "timeout"
    type AttrOrigin DockTransientGrabTimeoutPropertyInfo = DockTransientGrab
    attrGet = getDockTransientGrabTimeout
    attrSet = setDockTransientGrabTimeout
    attrTransfer _ v = do
        return v
    attrConstruct = constructDockTransientGrabTimeout
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.timeout"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#g:attr:timeout"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DockTransientGrab
type instance O.AttributeList DockTransientGrab = DockTransientGrabAttributeList
type DockTransientGrabAttributeList = ('[ '("timeout", DockTransientGrabTimeoutPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
dockTransientGrabTimeout :: AttrLabelProxy "timeout"
dockTransientGrabTimeout = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DockTransientGrab = DockTransientGrabSignalList
type DockTransientGrabSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method DockTransientGrab::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Dazzle" , name = "DockTransientGrab" })
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_new" dzl_dock_transient_grab_new :: 
    IO (Ptr DockTransientGrab)

-- | /No description available in the introspection data./
dockTransientGrabNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m DockTransientGrab
dockTransientGrabNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m DockTransientGrab
dockTransientGrabNew  = IO DockTransientGrab -> m DockTransientGrab
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DockTransientGrab -> m DockTransientGrab)
-> IO DockTransientGrab -> m DockTransientGrab
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
result <- IO (Ptr DockTransientGrab)
dzl_dock_transient_grab_new
    Text -> Ptr DockTransientGrab -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dockTransientGrabNew" Ptr DockTransientGrab
result
    DockTransientGrab
result' <- ((ManagedPtr DockTransientGrab -> DockTransientGrab)
-> Ptr DockTransientGrab -> IO DockTransientGrab
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DockTransientGrab -> DockTransientGrab
DockTransientGrab) Ptr DockTransientGrab
result
    DockTransientGrab -> IO DockTransientGrab
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DockTransientGrab
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method DockTransientGrab::acquire
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_acquire" dzl_dock_transient_grab_acquire :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    IO ()

-- | /No description available in the introspection data./
dockTransientGrabAcquire ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a) =>
    a
    -> m ()
dockTransientGrabAcquire :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockTransientGrab a) =>
a -> m ()
dockTransientGrabAcquire a
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DockTransientGrab -> IO ()
dzl_dock_transient_grab_acquire Ptr DockTransientGrab
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabAcquireMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDockTransientGrab a) => O.OverloadedMethod DockTransientGrabAcquireMethodInfo a signature where
    overloadedMethod = dockTransientGrabAcquire

instance O.OverloadedMethodInfo DockTransientGrabAcquireMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabAcquire",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabAcquire"
        })


#endif

-- method DockTransientGrab::add_item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType =
--               TInterface Name { namespace = "Dazzle" , name = "DockItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_add_item" dzl_dock_transient_grab_add_item :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    Ptr Dazzle.DockItem.DockItem ->         -- item : TInterface (Name {namespace = "Dazzle", name = "DockItem"})
    IO ()

-- | /No description available in the introspection data./
dockTransientGrabAddItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a, Dazzle.DockItem.IsDockItem b) =>
    a
    -> b
    -> m ()
dockTransientGrabAddItem :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDockTransientGrab a, IsDockItem b) =>
a -> b -> m ()
dockTransientGrabAddItem a
self b
item = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DockItem
item' <- b -> IO (Ptr DockItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    Ptr DockTransientGrab -> Ptr DockItem -> IO ()
dzl_dock_transient_grab_add_item Ptr DockTransientGrab
self' Ptr DockItem
item'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabAddItemMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDockTransientGrab a, Dazzle.DockItem.IsDockItem b) => O.OverloadedMethod DockTransientGrabAddItemMethodInfo a signature where
    overloadedMethod = dockTransientGrabAddItem

instance O.OverloadedMethodInfo DockTransientGrabAddItemMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabAddItem",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabAddItem"
        })


#endif

-- method DockTransientGrab::cancel
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_cancel" dzl_dock_transient_grab_cancel :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    IO ()

-- | /No description available in the introspection data./
dockTransientGrabCancel ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a) =>
    a
    -> m ()
dockTransientGrabCancel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockTransientGrab a) =>
a -> m ()
dockTransientGrabCancel a
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DockTransientGrab -> IO ()
dzl_dock_transient_grab_cancel Ptr DockTransientGrab
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabCancelMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDockTransientGrab a) => O.OverloadedMethod DockTransientGrabCancelMethodInfo a signature where
    overloadedMethod = dockTransientGrabCancel

instance O.OverloadedMethodInfo DockTransientGrabCancelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabCancel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabCancel"
        })


#endif

-- method DockTransientGrab::contains
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType =
--               TInterface Name { namespace = "Dazzle" , name = "DockItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_contains" dzl_dock_transient_grab_contains :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    Ptr Dazzle.DockItem.DockItem ->         -- item : TInterface (Name {namespace = "Dazzle", name = "DockItem"})
    IO CInt

-- | /No description available in the introspection data./
dockTransientGrabContains ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a, Dazzle.DockItem.IsDockItem b) =>
    a
    -> b
    -> m Bool
dockTransientGrabContains :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDockTransientGrab a, IsDockItem b) =>
a -> b -> m Bool
dockTransientGrabContains a
self b
item = IO Bool -> m Bool
forall a. IO a -> m a
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 DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DockItem
item' <- b -> IO (Ptr DockItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    CInt
result <- Ptr DockTransientGrab -> Ptr DockItem -> IO CInt
dzl_dock_transient_grab_contains Ptr DockTransientGrab
self' Ptr DockItem
item'
    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
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabContainsMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDockTransientGrab a, Dazzle.DockItem.IsDockItem b) => O.OverloadedMethod DockTransientGrabContainsMethodInfo a signature where
    overloadedMethod = dockTransientGrabContains

instance O.OverloadedMethodInfo DockTransientGrabContainsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabContains",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabContains"
        })


#endif

-- method DockTransientGrab::get_timeout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_get_timeout" dzl_dock_transient_grab_get_timeout :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    IO Word32

-- | /No description available in the introspection data./
dockTransientGrabGetTimeout ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a) =>
    a
    -> m Word32
dockTransientGrabGetTimeout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockTransientGrab a) =>
a -> m Word32
dockTransientGrabGetTimeout a
self = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word32
result <- Ptr DockTransientGrab -> IO Word32
dzl_dock_transient_grab_get_timeout Ptr DockTransientGrab
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabGetTimeoutMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDockTransientGrab a) => O.OverloadedMethod DockTransientGrabGetTimeoutMethodInfo a signature where
    overloadedMethod = dockTransientGrabGetTimeout

instance O.OverloadedMethodInfo DockTransientGrabGetTimeoutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabGetTimeout",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabGetTimeout"
        })


#endif

-- method DockTransientGrab::is_descendant
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_is_descendant" dzl_dock_transient_grab_is_descendant :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO CInt

-- | /No description available in the introspection data./
dockTransientGrabIsDescendant ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a, Gtk.Widget.IsWidget b) =>
    a
    -> b
    -> m Bool
dockTransientGrabIsDescendant :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDockTransientGrab a, IsWidget b) =>
a -> b -> m Bool
dockTransientGrabIsDescendant a
self b
widget = IO Bool -> m Bool
forall a. IO a -> m a
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 DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    CInt
result <- Ptr DockTransientGrab -> Ptr Widget -> IO CInt
dzl_dock_transient_grab_is_descendant Ptr DockTransientGrab
self' Ptr Widget
widget'
    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
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabIsDescendantMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDockTransientGrab a, Gtk.Widget.IsWidget b) => O.OverloadedMethod DockTransientGrabIsDescendantMethodInfo a signature where
    overloadedMethod = dockTransientGrabIsDescendant

instance O.OverloadedMethodInfo DockTransientGrabIsDescendantMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabIsDescendant",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabIsDescendant"
        })


#endif

-- method DockTransientGrab::release
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_release" dzl_dock_transient_grab_release :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    IO ()

-- | /No description available in the introspection data./
dockTransientGrabRelease ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a) =>
    a
    -> m ()
dockTransientGrabRelease :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockTransientGrab a) =>
a -> m ()
dockTransientGrabRelease a
self = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DockTransientGrab -> IO ()
dzl_dock_transient_grab_release Ptr DockTransientGrab
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabReleaseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDockTransientGrab a) => O.OverloadedMethod DockTransientGrabReleaseMethodInfo a signature where
    overloadedMethod = dockTransientGrabRelease

instance O.OverloadedMethodInfo DockTransientGrabReleaseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabRelease",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabRelease"
        })


#endif

-- method DockTransientGrab::remove_item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "item"
--           , argType =
--               TInterface Name { namespace = "Dazzle" , name = "DockItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_remove_item" dzl_dock_transient_grab_remove_item :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    Ptr Dazzle.DockItem.DockItem ->         -- item : TInterface (Name {namespace = "Dazzle", name = "DockItem"})
    IO ()

-- | /No description available in the introspection data./
dockTransientGrabRemoveItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a, Dazzle.DockItem.IsDockItem b) =>
    a
    -> b
    -> m ()
dockTransientGrabRemoveItem :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDockTransientGrab a, IsDockItem b) =>
a -> b -> m ()
dockTransientGrabRemoveItem a
self b
item = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DockItem
item' <- b -> IO (Ptr DockItem)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    Ptr DockTransientGrab -> Ptr DockItem -> IO ()
dzl_dock_transient_grab_remove_item Ptr DockTransientGrab
self' Ptr DockItem
item'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabRemoveItemMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDockTransientGrab a, Dazzle.DockItem.IsDockItem b) => O.OverloadedMethod DockTransientGrabRemoveItemMethodInfo a signature where
    overloadedMethod = dockTransientGrabRemoveItem

instance O.OverloadedMethodInfo DockTransientGrabRemoveItemMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabRemoveItem",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabRemoveItem"
        })


#endif

-- method DockTransientGrab::set_timeout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_set_timeout" dzl_dock_transient_grab_set_timeout :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    Word32 ->                               -- timeout : TBasicType TUInt
    IO ()

-- | /No description available in the introspection data./
dockTransientGrabSetTimeout ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a) =>
    a
    -> Word32
    -> m ()
dockTransientGrabSetTimeout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDockTransientGrab a) =>
a -> Word32 -> m ()
dockTransientGrabSetTimeout a
self Word32
timeout = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DockTransientGrab -> Word32 -> IO ()
dzl_dock_transient_grab_set_timeout Ptr DockTransientGrab
self' Word32
timeout
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabSetTimeoutMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDockTransientGrab a) => O.OverloadedMethod DockTransientGrabSetTimeoutMethodInfo a signature where
    overloadedMethod = dockTransientGrabSetTimeout

instance O.OverloadedMethodInfo DockTransientGrabSetTimeoutMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabSetTimeout",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabSetTimeout"
        })


#endif

-- method DockTransientGrab::steal_common_ancestors
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "other"
--           , argType =
--               TInterface
--                 Name { namespace = "Dazzle" , name = "DockTransientGrab" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_dock_transient_grab_steal_common_ancestors" dzl_dock_transient_grab_steal_common_ancestors :: 
    Ptr DockTransientGrab ->                -- self : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    Ptr DockTransientGrab ->                -- other : TInterface (Name {namespace = "Dazzle", name = "DockTransientGrab"})
    IO ()

-- | /No description available in the introspection data./
dockTransientGrabStealCommonAncestors ::
    (B.CallStack.HasCallStack, MonadIO m, IsDockTransientGrab a, IsDockTransientGrab b) =>
    a
    -> b
    -> m ()
dockTransientGrabStealCommonAncestors :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDockTransientGrab a,
 IsDockTransientGrab b) =>
a -> b -> m ()
dockTransientGrabStealCommonAncestors a
self b
other = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DockTransientGrab
self' <- a -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr DockTransientGrab
other' <- b -> IO (Ptr DockTransientGrab)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
other
    Ptr DockTransientGrab -> Ptr DockTransientGrab -> IO ()
dzl_dock_transient_grab_steal_common_ancestors Ptr DockTransientGrab
self' Ptr DockTransientGrab
other'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
other
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DockTransientGrabStealCommonAncestorsMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDockTransientGrab a, IsDockTransientGrab b) => O.OverloadedMethod DockTransientGrabStealCommonAncestorsMethodInfo a signature where
    overloadedMethod = dockTransientGrabStealCommonAncestors

instance O.OverloadedMethodInfo DockTransientGrabStealCommonAncestorsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.DockTransientGrab.dockTransientGrabStealCommonAncestors",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-DockTransientGrab.html#v:dockTransientGrabStealCommonAncestors"
        })


#endif