{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GtkWidgetPath is a boxed type that represents a widget hierarchy from
-- the topmost widget, typically a toplevel, to any child. This widget
-- path abstraction is used in t'GI.Gtk.Objects.StyleContext.StyleContext' on behalf of the real
-- widget in order to query style information.
-- 
-- If you are using GTK+ widgets, you probably will not need to use
-- this API directly, as there is 'GI.Gtk.Objects.Widget.widgetGetPath', and the style
-- context returned by 'GI.Gtk.Objects.Widget.widgetGetStyleContext' will be automatically
-- updated on widget hierarchy changes.
-- 
-- The widget path generation is generally simple:
-- 
-- == Defining a button within a window
-- 
-- 
-- === /C code/
-- >
-- >{
-- >  GtkWidgetPath *path;
-- >
-- >  path = gtk_widget_path_new ();
-- >  gtk_widget_path_append_type (path, GTK_TYPE_WINDOW);
-- >  gtk_widget_path_append_type (path, GTK_TYPE_BUTTON);
-- >}
-- 
-- 
-- Although more complex information, such as widget names, or
-- different classes (property that may be used by other widget
-- types) and intermediate regions may be included:
-- 
-- == Defining the first tab widget in a notebook
-- 
-- 
-- === /C code/
-- >
-- >{
-- >  GtkWidgetPath *path;
-- >  guint pos;
-- >
-- >  path = gtk_widget_path_new ();
-- >
-- >  pos = gtk_widget_path_append_type (path, GTK_TYPE_NOTEBOOK);
-- >  gtk_widget_path_iter_add_region (path, pos, "tab", GTK_REGION_EVEN | GTK_REGION_FIRST);
-- >
-- >  pos = gtk_widget_path_append_type (path, GTK_TYPE_LABEL);
-- >  gtk_widget_path_iter_set_name (path, pos, "first tab label");
-- >}
-- 
-- 
-- All this information will be used to match the style information
-- that applies to the described widget.

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

module GI.Gtk.Structs.WidgetPath
    ( 

-- * Exported types
    WidgetPath(..)                          ,
    noWidgetPath                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveWidgetPathMethod                 ,
#endif


-- ** appendForWidget #method:appendForWidget#

#if defined(ENABLE_OVERLOADING)
    WidgetPathAppendForWidgetMethodInfo     ,
#endif
    widgetPathAppendForWidget               ,


-- ** appendType #method:appendType#

#if defined(ENABLE_OVERLOADING)
    WidgetPathAppendTypeMethodInfo          ,
#endif
    widgetPathAppendType                    ,


-- ** appendWithSiblings #method:appendWithSiblings#

#if defined(ENABLE_OVERLOADING)
    WidgetPathAppendWithSiblingsMethodInfo  ,
#endif
    widgetPathAppendWithSiblings            ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    WidgetPathCopyMethodInfo                ,
#endif
    widgetPathCopy                          ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    WidgetPathFreeMethodInfo                ,
#endif
    widgetPathFree                          ,


-- ** getObjectType #method:getObjectType#

#if defined(ENABLE_OVERLOADING)
    WidgetPathGetObjectTypeMethodInfo       ,
#endif
    widgetPathGetObjectType                 ,


-- ** hasParent #method:hasParent#

#if defined(ENABLE_OVERLOADING)
    WidgetPathHasParentMethodInfo           ,
#endif
    widgetPathHasParent                     ,


-- ** isType #method:isType#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIsTypeMethodInfo              ,
#endif
    widgetPathIsType                        ,


-- ** iterAddClass #method:iterAddClass#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterAddClassMethodInfo        ,
#endif
    widgetPathIterAddClass                  ,


-- ** iterAddRegion #method:iterAddRegion#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterAddRegionMethodInfo       ,
#endif
    widgetPathIterAddRegion                 ,


-- ** iterClearClasses #method:iterClearClasses#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterClearClassesMethodInfo    ,
#endif
    widgetPathIterClearClasses              ,


-- ** iterClearRegions #method:iterClearRegions#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterClearRegionsMethodInfo    ,
#endif
    widgetPathIterClearRegions              ,


-- ** iterGetName #method:iterGetName#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterGetNameMethodInfo         ,
#endif
    widgetPathIterGetName                   ,


-- ** iterGetObjectName #method:iterGetObjectName#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterGetObjectNameMethodInfo   ,
#endif
    widgetPathIterGetObjectName             ,


-- ** iterGetObjectType #method:iterGetObjectType#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterGetObjectTypeMethodInfo   ,
#endif
    widgetPathIterGetObjectType             ,


-- ** iterGetSiblingIndex #method:iterGetSiblingIndex#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterGetSiblingIndexMethodInfo ,
#endif
    widgetPathIterGetSiblingIndex           ,


-- ** iterGetSiblings #method:iterGetSiblings#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterGetSiblingsMethodInfo     ,
#endif
    widgetPathIterGetSiblings               ,


-- ** iterGetState #method:iterGetState#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterGetStateMethodInfo        ,
#endif
    widgetPathIterGetState                  ,


-- ** iterHasClass #method:iterHasClass#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterHasClassMethodInfo        ,
#endif
    widgetPathIterHasClass                  ,


-- ** iterHasName #method:iterHasName#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterHasNameMethodInfo         ,
#endif
    widgetPathIterHasName                   ,


-- ** iterHasQclass #method:iterHasQclass#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterHasQclassMethodInfo       ,
#endif
    widgetPathIterHasQclass                 ,


-- ** iterHasQname #method:iterHasQname#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterHasQnameMethodInfo        ,
#endif
    widgetPathIterHasQname                  ,


-- ** iterHasQregion #method:iterHasQregion#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterHasQregionMethodInfo      ,
#endif
    widgetPathIterHasQregion                ,


-- ** iterHasRegion #method:iterHasRegion#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterHasRegionMethodInfo       ,
#endif
    widgetPathIterHasRegion                 ,


-- ** iterListClasses #method:iterListClasses#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterListClassesMethodInfo     ,
#endif
    widgetPathIterListClasses               ,


-- ** iterListRegions #method:iterListRegions#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterListRegionsMethodInfo     ,
#endif
    widgetPathIterListRegions               ,


-- ** iterRemoveClass #method:iterRemoveClass#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterRemoveClassMethodInfo     ,
#endif
    widgetPathIterRemoveClass               ,


-- ** iterRemoveRegion #method:iterRemoveRegion#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterRemoveRegionMethodInfo    ,
#endif
    widgetPathIterRemoveRegion              ,


-- ** iterSetName #method:iterSetName#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterSetNameMethodInfo         ,
#endif
    widgetPathIterSetName                   ,


-- ** iterSetObjectName #method:iterSetObjectName#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterSetObjectNameMethodInfo   ,
#endif
    widgetPathIterSetObjectName             ,


-- ** iterSetObjectType #method:iterSetObjectType#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterSetObjectTypeMethodInfo   ,
#endif
    widgetPathIterSetObjectType             ,


-- ** iterSetState #method:iterSetState#

#if defined(ENABLE_OVERLOADING)
    WidgetPathIterSetStateMethodInfo        ,
#endif
    widgetPathIterSetState                  ,


-- ** length #method:length#

#if defined(ENABLE_OVERLOADING)
    WidgetPathLengthMethodInfo              ,
#endif
    widgetPathLength                        ,


-- ** new #method:new#

    widgetPathNew                           ,


-- ** prependType #method:prependType#

#if defined(ENABLE_OVERLOADING)
    WidgetPathPrependTypeMethodInfo         ,
#endif
    widgetPathPrependType                   ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    WidgetPathRefMethodInfo                 ,
#endif
    widgetPathRef                           ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    WidgetPathToStringMethodInfo            ,
#endif
    widgetPathToString                      ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    WidgetPathUnrefMethodInfo               ,
#endif
    widgetPathUnref                         ,




    ) 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.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

-- | Memory-managed wrapper type.
newtype WidgetPath = WidgetPath (ManagedPtr WidgetPath)
    deriving (WidgetPath -> WidgetPath -> Bool
(WidgetPath -> WidgetPath -> Bool)
-> (WidgetPath -> WidgetPath -> Bool) -> Eq WidgetPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetPath -> WidgetPath -> Bool
$c/= :: WidgetPath -> WidgetPath -> Bool
== :: WidgetPath -> WidgetPath -> Bool
$c== :: WidgetPath -> WidgetPath -> Bool
Eq)
foreign import ccall "gtk_widget_path_get_type" c_gtk_widget_path_get_type :: 
    IO GType

instance BoxedObject WidgetPath where
    boxedType :: WidgetPath -> IO GType
boxedType _ = IO GType
c_gtk_widget_path_get_type

-- | Convert 'WidgetPath' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue WidgetPath where
    toGValue :: WidgetPath -> IO GValue
toGValue o :: WidgetPath
o = do
        GType
gtype <- IO GType
c_gtk_widget_path_get_type
        WidgetPath -> (Ptr WidgetPath -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr WidgetPath
o (GType
-> (GValue -> Ptr WidgetPath -> IO ())
-> Ptr WidgetPath
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr WidgetPath -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO WidgetPath
fromGValue gv :: GValue
gv = do
        Ptr WidgetPath
ptr <- GValue -> IO (Ptr WidgetPath)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr WidgetPath)
        (ManagedPtr WidgetPath -> WidgetPath)
-> Ptr WidgetPath -> IO WidgetPath
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr WidgetPath -> WidgetPath
WidgetPath Ptr WidgetPath
ptr
        
    

-- | A convenience alias for `Nothing` :: `Maybe` `WidgetPath`.
noWidgetPath :: Maybe WidgetPath
noWidgetPath :: Maybe WidgetPath
noWidgetPath = Maybe WidgetPath
forall a. Maybe a
Nothing


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

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

foreign import ccall "gtk_widget_path_new" gtk_widget_path_new :: 
    IO (Ptr WidgetPath)

-- | Returns an empty widget path.
-- 
-- /Since: 3.0/
widgetPathNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m WidgetPath
    -- ^ __Returns:__ A newly created, empty, t'GI.Gtk.Structs.WidgetPath.WidgetPath'
widgetPathNew :: m WidgetPath
widgetPathNew  = IO WidgetPath -> m WidgetPath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WidgetPath -> m WidgetPath) -> IO WidgetPath -> m WidgetPath
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
result <- IO (Ptr WidgetPath)
gtk_widget_path_new
    Text -> Ptr WidgetPath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "widgetPathNew" Ptr WidgetPath
result
    WidgetPath
result' <- ((ManagedPtr WidgetPath -> WidgetPath)
-> Ptr WidgetPath -> IO WidgetPath
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr WidgetPath -> WidgetPath
WidgetPath) Ptr WidgetPath
result
    WidgetPath -> IO WidgetPath
forall (m :: * -> *) a. Monad m => a -> m a
return WidgetPath
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method WidgetPath::append_for_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a widget path" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the widget to append to the widget path"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_append_for_widget" gtk_widget_path_append_for_widget :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO Int32

-- | Appends the data from /@widget@/ to the widget hierarchy represented
-- by /@path@/. This function is a shortcut for adding information from
-- /@widget@/ to the given /@path@/. This includes setting the name or
-- adding the style classes from /@widget@/.
-- 
-- /Since: 3.2/
widgetPathAppendForWidget ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Widget.IsWidget a) =>
    WidgetPath
    -- ^ /@path@/: a widget path
    -> a
    -- ^ /@widget@/: the widget to append to the widget path
    -> m Int32
    -- ^ __Returns:__ the position where the data was inserted
widgetPathAppendForWidget :: WidgetPath -> a -> m Int32
widgetPathAppendForWidget path :: WidgetPath
path widget :: a
widget = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr Widget
widget' <- a -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
widget
    Int32
result <- Ptr WidgetPath -> Ptr Widget -> IO Int32
gtk_widget_path_append_for_widget Ptr WidgetPath
path' Ptr Widget
widget'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
widget
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data WidgetPathAppendForWidgetMethodInfo
instance (signature ~ (a -> m Int32), MonadIO m, Gtk.Widget.IsWidget a) => O.MethodInfo WidgetPathAppendForWidgetMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathAppendForWidget

#endif

-- method WidgetPath::append_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "widget type to append"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_append_type" gtk_widget_path_append_type :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    CGType ->                               -- type : TBasicType TGType
    IO Int32

-- | Appends a widget type to the widget hierarchy represented by /@path@/.
-- 
-- /Since: 3.0/
widgetPathAppendType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> GType
    -- ^ /@type@/: widget type to append
    -> m Int32
    -- ^ __Returns:__ the position where the element was inserted
widgetPathAppendType :: WidgetPath -> GType -> m Int32
widgetPathAppendType path :: WidgetPath
path type_ :: GType
type_ = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
    Int32
result <- Ptr WidgetPath -> CGType -> IO Int32
gtk_widget_path_append_type Ptr WidgetPath
path' CGType
type_'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data WidgetPathAppendTypeMethodInfo
instance (signature ~ (GType -> m Int32), MonadIO m) => O.MethodInfo WidgetPathAppendTypeMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathAppendType

#endif

-- method WidgetPath::append_with_siblings
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the widget path to append to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "siblings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a widget path describing a list of siblings. This path\n  may not contain any siblings itself and it must not be modified\n  afterwards."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sibling_index"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "index into @siblings for where the added element is\n  positioned."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_append_with_siblings" gtk_widget_path_append_with_siblings :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Ptr WidgetPath ->                       -- siblings : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Word32 ->                               -- sibling_index : TBasicType TUInt
    IO Int32

-- | Appends a widget type with all its siblings to the widget hierarchy
-- represented by /@path@/. Using this function instead of
-- 'GI.Gtk.Structs.WidgetPath.widgetPathAppendType' will allow the CSS theming to use
-- sibling matches in selectors and apply :nth-@/child()/@ pseudo classes.
-- In turn, it requires a lot more care in widget implementations as
-- widgets need to make sure to call 'GI.Gtk.Objects.Widget.widgetResetStyle' on all
-- involved widgets when the /@siblings@/ path changes.
-- 
-- /Since: 3.2/
widgetPathAppendWithSiblings ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: the widget path to append to
    -> WidgetPath
    -- ^ /@siblings@/: a widget path describing a list of siblings. This path
    --   may not contain any siblings itself and it must not be modified
    --   afterwards.
    -> Word32
    -- ^ /@siblingIndex@/: index into /@siblings@/ for where the added element is
    --   positioned.
    -> m Int32
    -- ^ __Returns:__ the position where the element was inserted.
widgetPathAppendWithSiblings :: WidgetPath -> WidgetPath -> Word32 -> m Int32
widgetPathAppendWithSiblings path :: WidgetPath
path siblings :: WidgetPath
siblings siblingIndex :: Word32
siblingIndex = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr WidgetPath
siblings' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
siblings
    Int32
result <- Ptr WidgetPath -> Ptr WidgetPath -> Word32 -> IO Int32
gtk_widget_path_append_with_siblings Ptr WidgetPath
path' Ptr WidgetPath
siblings' Word32
siblingIndex
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
siblings
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data WidgetPathAppendWithSiblingsMethodInfo
instance (signature ~ (WidgetPath -> Word32 -> m Int32), MonadIO m) => O.MethodInfo WidgetPathAppendWithSiblingsMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathAppendWithSiblings

#endif

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

foreign import ccall "gtk_widget_path_copy" gtk_widget_path_copy :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO (Ptr WidgetPath)

-- | Returns a copy of /@path@/
-- 
-- /Since: 3.0/
widgetPathCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> m WidgetPath
    -- ^ __Returns:__ a copy of /@path@/
widgetPathCopy :: WidgetPath -> m WidgetPath
widgetPathCopy path :: WidgetPath
path = IO WidgetPath -> m WidgetPath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WidgetPath -> m WidgetPath) -> IO WidgetPath -> m WidgetPath
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr WidgetPath
result <- Ptr WidgetPath -> IO (Ptr WidgetPath)
gtk_widget_path_copy Ptr WidgetPath
path'
    Text -> Ptr WidgetPath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "widgetPathCopy" Ptr WidgetPath
result
    WidgetPath
result' <- ((ManagedPtr WidgetPath -> WidgetPath)
-> Ptr WidgetPath -> IO WidgetPath
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr WidgetPath -> WidgetPath
WidgetPath) Ptr WidgetPath
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    WidgetPath -> IO WidgetPath
forall (m :: * -> *) a. Monad m => a -> m a
return WidgetPath
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathCopyMethodInfo
instance (signature ~ (m WidgetPath), MonadIO m) => O.MethodInfo WidgetPathCopyMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathCopy

#endif

-- method WidgetPath::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_free" gtk_widget_path_free :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO ()

-- | Decrements the reference count on /@path@/, freeing the structure
-- if the reference count reaches 0.
-- 
-- /Since: 3.0/
widgetPathFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> m ()
widgetPathFree :: WidgetPath -> m ()
widgetPathFree path :: WidgetPath
path = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr WidgetPath -> IO ()
gtk_widget_path_free Ptr WidgetPath
path'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo WidgetPathFreeMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathFree

#endif

-- method WidgetPath::get_object_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidget" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_get_object_type" gtk_widget_path_get_object_type :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO CGType

-- | Returns the topmost object type, that is, the object type this path
-- is representing.
-- 
-- /Since: 3.0/
widgetPathGetObjectType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Objects.Widget.Widget'
    -> m GType
    -- ^ __Returns:__ The object type
widgetPathGetObjectType :: WidgetPath -> m GType
widgetPathGetObjectType path :: WidgetPath
path = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CGType
result <- Ptr WidgetPath -> IO CGType
gtk_widget_path_get_object_type Ptr WidgetPath
path'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathGetObjectTypeMethodInfo
instance (signature ~ (m GType), MonadIO m) => O.MethodInfo WidgetPathGetObjectTypeMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathGetObjectType

#endif

-- method WidgetPath::has_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "widget type to check in parents"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_has_parent" gtk_widget_path_has_parent :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    CGType ->                               -- type : TBasicType TGType
    IO CInt

-- | Returns 'P.True' if any of the parents of the widget represented
-- in /@path@/ is of type /@type@/, or any subtype of it.
-- 
-- /Since: 3.0/
widgetPathHasParent ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> GType
    -- ^ /@type@/: widget type to check in parents
    -> m Bool
    -- ^ __Returns:__ 'P.True' if any parent is of type /@type@/
widgetPathHasParent :: WidgetPath -> GType -> m Bool
widgetPathHasParent path :: WidgetPath
path type_ :: GType
type_ = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
    CInt
result <- Ptr WidgetPath -> CGType -> IO CInt
gtk_widget_path_has_parent Ptr WidgetPath
path' CGType
type_'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathHasParentMethodInfo
instance (signature ~ (GType -> m Bool), MonadIO m) => O.MethodInfo WidgetPathHasParentMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathHasParent

#endif

-- method WidgetPath::is_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "widget type to match"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_is_type" gtk_widget_path_is_type :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    CGType ->                               -- type : TBasicType TGType
    IO CInt

-- | Returns 'P.True' if the widget type represented by this path
-- is /@type@/, or a subtype of it.
-- 
-- /Since: 3.0/
widgetPathIsType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> GType
    -- ^ /@type@/: widget type to match
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the widget represented by /@path@/ is of type /@type@/
widgetPathIsType :: WidgetPath -> GType -> m Bool
widgetPathIsType path :: WidgetPath
path type_ :: GType
type_ = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
    CInt
result <- Ptr WidgetPath -> CGType -> IO CInt
gtk_widget_path_is_type Ptr WidgetPath
path' CGType
type_'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathIsTypeMethodInfo
instance (signature ~ (GType -> m Bool), MonadIO m) => O.MethodInfo WidgetPathIsTypeMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIsType

#endif

-- method WidgetPath::iter_add_class
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidget" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a class name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_add_class" gtk_widget_path_iter_add_class :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Adds the class /@name@/ to the widget at position /@pos@/ in
-- the hierarchy defined in /@path@/. See
-- 'GI.Gtk.Objects.StyleContext.styleContextAddClass'.
-- 
-- /Since: 3.0/
widgetPathIterAddClass ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Objects.Widget.Widget'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> T.Text
    -- ^ /@name@/: a class name
    -> m ()
widgetPathIterAddClass :: WidgetPath -> Int32 -> Text -> m ()
widgetPathIterAddClass path :: WidgetPath
path pos :: Int32
pos name :: Text
name = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr WidgetPath -> Int32 -> CString -> IO ()
gtk_widget_path_iter_add_class Ptr WidgetPath
path' Int32
pos CString
name'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterAddClassMethodInfo
instance (signature ~ (Int32 -> T.Text -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterAddClassMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterAddClass

#endif

-- method WidgetPath::iter_add_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "region name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RegionFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags affecting the region"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_add_region" gtk_widget_path_iter_add_region :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gtk", name = "RegionFlags"})
    IO ()

{-# DEPRECATED widgetPathIterAddRegion ["(Since version 3.14)","The use of regions is deprecated."] #-}
-- | Adds the region /@name@/ to the widget at position /@pos@/ in
-- the hierarchy defined in /@path@/. See
-- 'GI.Gtk.Objects.StyleContext.styleContextAddRegion'.
-- 
-- Region names must only contain lowercase letters
-- and “-”, starting always with a lowercase letter.
-- 
-- /Since: 3.0/
widgetPathIterAddRegion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> T.Text
    -- ^ /@name@/: region name
    -> [Gtk.Flags.RegionFlags]
    -- ^ /@flags@/: flags affecting the region
    -> m ()
widgetPathIterAddRegion :: WidgetPath -> Int32 -> Text -> [RegionFlags] -> m ()
widgetPathIterAddRegion path :: WidgetPath
path pos :: Int32
pos name :: Text
name flags :: [RegionFlags]
flags = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    let flags' :: CUInt
flags' = [RegionFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [RegionFlags]
flags
    Ptr WidgetPath -> Int32 -> CString -> CUInt -> IO ()
gtk_widget_path_iter_add_region Ptr WidgetPath
path' Int32
pos CString
name' CUInt
flags'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterAddRegionMethodInfo
instance (signature ~ (Int32 -> T.Text -> [Gtk.Flags.RegionFlags] -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterAddRegionMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterAddRegion

#endif

-- method WidgetPath::iter_clear_classes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidget" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_clear_classes" gtk_widget_path_iter_clear_classes :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO ()

-- | Removes all classes from the widget at position /@pos@/ in the
-- hierarchy defined in /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterClearClasses ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Objects.Widget.Widget'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> m ()
widgetPathIterClearClasses :: WidgetPath -> Int32 -> m ()
widgetPathIterClearClasses path :: WidgetPath
path pos :: Int32
pos = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr WidgetPath -> Int32 -> IO ()
gtk_widget_path_iter_clear_classes Ptr WidgetPath
path' Int32
pos
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterClearClassesMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterClearClassesMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterClearClasses

#endif

-- method WidgetPath::iter_clear_regions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_clear_regions" gtk_widget_path_iter_clear_regions :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO ()

{-# DEPRECATED widgetPathIterClearRegions ["(Since version 3.14)","The use of regions is deprecated."] #-}
-- | Removes all regions from the widget at position /@pos@/ in the
-- hierarchy defined in /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterClearRegions ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> m ()
widgetPathIterClearRegions :: WidgetPath -> Int32 -> m ()
widgetPathIterClearRegions path :: WidgetPath
path pos :: Int32
pos = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr WidgetPath -> Int32 -> IO ()
gtk_widget_path_iter_clear_regions Ptr WidgetPath
path' Int32
pos
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterClearRegionsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterClearRegionsMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterClearRegions

#endif

-- method WidgetPath::iter_get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "position to get the widget name for, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_get_name" gtk_widget_path_iter_get_name :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO CString

-- | Returns the name corresponding to the widget found at
-- the position /@pos@/ in the widget hierarchy defined by
-- /@path@/
widgetPathIterGetName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to get the widget name for, -1 for the path head
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The widget name, or 'P.Nothing' if none was set.
widgetPathIterGetName :: WidgetPath -> Int32 -> m (Maybe Text)
widgetPathIterGetName path :: WidgetPath
path pos :: Int32
pos = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
result <- Ptr WidgetPath -> Int32 -> IO CString
gtk_widget_path_iter_get_name Ptr WidgetPath
path' Int32
pos
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterGetNameMethodInfo
instance (signature ~ (Int32 -> m (Maybe T.Text)), MonadIO m) => O.MethodInfo WidgetPathIterGetNameMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterGetName

#endif

-- method WidgetPath::iter_get_object_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "position to get the object name for, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_get_object_name" gtk_widget_path_iter_get_object_name :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO CString

-- | Returns the object name that is at position /@pos@/ in the widget
-- hierarchy defined in /@path@/.
-- 
-- /Since: 3.20/
widgetPathIterGetObjectName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to get the object name for, -1 for the path head
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the name or 'P.Nothing'
widgetPathIterGetObjectName :: WidgetPath -> Int32 -> m (Maybe Text)
widgetPathIterGetObjectName path :: WidgetPath
path pos :: Int32
pos = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
result <- Ptr WidgetPath -> Int32 -> IO CString
gtk_widget_path_iter_get_object_name Ptr WidgetPath
path' Int32
pos
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterGetObjectNameMethodInfo
instance (signature ~ (Int32 -> m (Maybe T.Text)), MonadIO m) => O.MethodInfo WidgetPathIterGetObjectNameMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterGetObjectName

#endif

-- method WidgetPath::iter_get_object_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "position to get the object type for, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_get_object_type" gtk_widget_path_iter_get_object_type :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO CGType

-- | Returns the object t'GType' that is at position /@pos@/ in the widget
-- hierarchy defined in /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterGetObjectType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to get the object type for, -1 for the path head
    -> m GType
    -- ^ __Returns:__ a widget type
widgetPathIterGetObjectType :: WidgetPath -> Int32 -> m GType
widgetPathIterGetObjectType path :: WidgetPath
path pos :: Int32
pos = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CGType
result <- Ptr WidgetPath -> Int32 -> IO CGType
gtk_widget_path_iter_get_object_type Ptr WidgetPath
path' Int32
pos
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterGetObjectTypeMethodInfo
instance (signature ~ (Int32 -> m GType), MonadIO m) => O.MethodInfo WidgetPathIterGetObjectTypeMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterGetObjectType

#endif

-- method WidgetPath::iter_get_sibling_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "position to get the sibling index for, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_get_sibling_index" gtk_widget_path_iter_get_sibling_index :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO Word32

-- | Returns the index into the list of siblings for the element at /@pos@/ as
-- returned by 'GI.Gtk.Structs.WidgetPath.widgetPathIterGetSiblings'. If that function would
-- return 'P.Nothing' because the element at /@pos@/ has no siblings, this function
-- will return 0.
widgetPathIterGetSiblingIndex ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to get the sibling index for, -1 for the path head
    -> m Word32
    -- ^ __Returns:__ 0 or the index into the list of siblings for the element at /@pos@/.
widgetPathIterGetSiblingIndex :: WidgetPath -> Int32 -> m Word32
widgetPathIterGetSiblingIndex path :: WidgetPath
path pos :: Int32
pos = IO Word32 -> m Word32
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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Word32
result <- Ptr WidgetPath -> Int32 -> IO Word32
gtk_widget_path_iter_get_sibling_index Ptr WidgetPath
path' Int32
pos
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterGetSiblingIndexMethodInfo
instance (signature ~ (Int32 -> m Word32), MonadIO m) => O.MethodInfo WidgetPathIterGetSiblingIndexMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterGetSiblingIndex

#endif

-- method WidgetPath::iter_get_siblings
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "position to get the siblings for, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "WidgetPath" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_get_siblings" gtk_widget_path_iter_get_siblings :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO (Ptr WidgetPath)

-- | Returns the list of siblings for the element at /@pos@/. If the element
-- was not added with siblings, 'P.Nothing' is returned.
widgetPathIterGetSiblings ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to get the siblings for, -1 for the path head
    -> m WidgetPath
    -- ^ __Returns:__ 'P.Nothing' or the list of siblings for the element at /@pos@/.
widgetPathIterGetSiblings :: WidgetPath -> Int32 -> m WidgetPath
widgetPathIterGetSiblings path :: WidgetPath
path pos :: Int32
pos = IO WidgetPath -> m WidgetPath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WidgetPath -> m WidgetPath) -> IO WidgetPath -> m WidgetPath
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr WidgetPath
result <- Ptr WidgetPath -> Int32 -> IO (Ptr WidgetPath)
gtk_widget_path_iter_get_siblings Ptr WidgetPath
path' Int32
pos
    Text -> Ptr WidgetPath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "widgetPathIterGetSiblings" Ptr WidgetPath
result
    WidgetPath
result' <- ((ManagedPtr WidgetPath -> WidgetPath)
-> Ptr WidgetPath -> IO WidgetPath
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr WidgetPath -> WidgetPath
WidgetPath) Ptr WidgetPath
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    WidgetPath -> IO WidgetPath
forall (m :: * -> *) a. Monad m => a -> m a
return WidgetPath
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterGetSiblingsMethodInfo
instance (signature ~ (Int32 -> m WidgetPath), MonadIO m) => O.MethodInfo WidgetPathIterGetSiblingsMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterGetSiblings

#endif

-- method WidgetPath::iter_get_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "position to get the state for, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "StateFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_get_state" gtk_widget_path_iter_get_state :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO CUInt

-- | Returns the state flags corresponding to the widget found at
-- the position /@pos@/ in the widget hierarchy defined by
-- /@path@/
-- 
-- /Since: 3.14/
widgetPathIterGetState ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to get the state for, -1 for the path head
    -> m [Gtk.Flags.StateFlags]
    -- ^ __Returns:__ The state flags
widgetPathIterGetState :: WidgetPath -> Int32 -> m [StateFlags]
widgetPathIterGetState path :: WidgetPath
path pos :: Int32
pos = IO [StateFlags] -> m [StateFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [StateFlags] -> m [StateFlags])
-> IO [StateFlags] -> m [StateFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CUInt
result <- Ptr WidgetPath -> Int32 -> IO CUInt
gtk_widget_path_iter_get_state Ptr WidgetPath
path' Int32
pos
    let result' :: [StateFlags]
result' = CUInt -> [StateFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    [StateFlags] -> IO [StateFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [StateFlags]
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterGetStateMethodInfo
instance (signature ~ (Int32 -> m [Gtk.Flags.StateFlags]), MonadIO m) => O.MethodInfo WidgetPathIterGetStateMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterGetState

#endif

-- method WidgetPath::iter_has_class
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to query, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "class name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_has_class" gtk_widget_path_iter_has_class :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    IO CInt

-- | Returns 'P.True' if the widget at position /@pos@/ has the class /@name@/
-- defined, 'P.False' otherwise.
-- 
-- /Since: 3.0/
widgetPathIterHasClass ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to query, -1 for the path head
    -> T.Text
    -- ^ /@name@/: class name
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the class /@name@/ is defined for the widget at /@pos@/
widgetPathIterHasClass :: WidgetPath -> Int32 -> Text -> m Bool
widgetPathIterHasClass path :: WidgetPath
path pos :: Int32
pos name :: Text
name = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    CInt
result <- Ptr WidgetPath -> Int32 -> CString -> IO CInt
gtk_widget_path_iter_has_class Ptr WidgetPath
path' Int32
pos CString
name'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterHasClassMethodInfo
instance (signature ~ (Int32 -> T.Text -> m Bool), MonadIO m) => O.MethodInfo WidgetPathIterHasClassMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterHasClass

#endif

-- method WidgetPath::iter_has_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to query, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a widget name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_has_name" gtk_widget_path_iter_has_name :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    IO CInt

-- | Returns 'P.True' if the widget at position /@pos@/ has the name /@name@/,
-- 'P.False' otherwise.
-- 
-- /Since: 3.0/
widgetPathIterHasName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to query, -1 for the path head
    -> T.Text
    -- ^ /@name@/: a widget name
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the widget at /@pos@/ has this name
widgetPathIterHasName :: WidgetPath -> Int32 -> Text -> m Bool
widgetPathIterHasName path :: WidgetPath
path pos :: Int32
pos name :: Text
name = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    CInt
result <- Ptr WidgetPath -> Int32 -> CString -> IO CInt
gtk_widget_path_iter_has_name Ptr WidgetPath
path' Int32
pos CString
name'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterHasNameMethodInfo
instance (signature ~ (Int32 -> T.Text -> m Bool), MonadIO m) => O.MethodInfo WidgetPathIterHasNameMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterHasName

#endif

-- method WidgetPath::iter_has_qclass
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to query, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "qname"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "class name as a #GQuark"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_has_qclass" gtk_widget_path_iter_has_qclass :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    Word32 ->                               -- qname : TBasicType TUInt32
    IO CInt

-- | See 'GI.Gtk.Structs.WidgetPath.widgetPathIterHasClass'. This is a version that operates
-- with GQuarks.
-- 
-- /Since: 3.0/
widgetPathIterHasQclass ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to query, -1 for the path head
    -> Word32
    -- ^ /@qname@/: class name as a @/GQuark/@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the widget at /@pos@/ has the class defined.
widgetPathIterHasQclass :: WidgetPath -> Int32 -> Word32 -> m Bool
widgetPathIterHasQclass path :: WidgetPath
path pos :: Int32
pos qname :: Word32
qname = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CInt
result <- Ptr WidgetPath -> Int32 -> Word32 -> IO CInt
gtk_widget_path_iter_has_qclass Ptr WidgetPath
path' Int32
pos Word32
qname
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterHasQclassMethodInfo
instance (signature ~ (Int32 -> Word32 -> m Bool), MonadIO m) => O.MethodInfo WidgetPathIterHasQclassMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterHasQclass

#endif

-- method WidgetPath::iter_has_qname
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to query, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "qname"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "widget name as a #GQuark"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_has_qname" gtk_widget_path_iter_has_qname :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    Word32 ->                               -- qname : TBasicType TUInt32
    IO CInt

-- | See 'GI.Gtk.Structs.WidgetPath.widgetPathIterHasName'. This is a version
-- that operates on @/GQuarks/@.
-- 
-- /Since: 3.0/
widgetPathIterHasQname ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to query, -1 for the path head
    -> Word32
    -- ^ /@qname@/: widget name as a @/GQuark/@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the widget at /@pos@/ has this name
widgetPathIterHasQname :: WidgetPath -> Int32 -> Word32 -> m Bool
widgetPathIterHasQname path :: WidgetPath
path pos :: Int32
pos qname :: Word32
qname = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CInt
result <- Ptr WidgetPath -> Int32 -> Word32 -> IO CInt
gtk_widget_path_iter_has_qname Ptr WidgetPath
path' Int32
pos Word32
qname
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterHasQnameMethodInfo
instance (signature ~ (Int32 -> Word32 -> m Bool), MonadIO m) => O.MethodInfo WidgetPathIterHasQnameMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterHasQname

#endif

-- method WidgetPath::iter_has_qregion
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to query, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "qname"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "region name as a #GQuark"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RegionFlags" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the region flags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_has_qregion" gtk_widget_path_iter_has_qregion :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    Word32 ->                               -- qname : TBasicType TUInt32
    Ptr CUInt ->                            -- flags : TInterface (Name {namespace = "Gtk", name = "RegionFlags"})
    IO CInt

{-# DEPRECATED widgetPathIterHasQregion ["(Since version 3.14)","The use of regions is deprecated."] #-}
-- | See 'GI.Gtk.Structs.WidgetPath.widgetPathIterHasRegion'. This is a version that operates
-- with GQuarks.
-- 
-- /Since: 3.0/
widgetPathIterHasQregion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to query, -1 for the path head
    -> Word32
    -- ^ /@qname@/: region name as a @/GQuark/@
    -> m ((Bool, [Gtk.Flags.RegionFlags]))
    -- ^ __Returns:__ 'P.True' if the widget at /@pos@/ has the region defined.
widgetPathIterHasQregion :: WidgetPath -> Int32 -> Word32 -> m (Bool, [RegionFlags])
widgetPathIterHasQregion path :: WidgetPath
path pos :: Int32
pos qname :: Word32
qname = IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags]))
-> IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags])
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr CUInt
flags <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    CInt
result <- Ptr WidgetPath -> Int32 -> Word32 -> Ptr CUInt -> IO CInt
gtk_widget_path_iter_has_qregion Ptr WidgetPath
path' Int32
pos Word32
qname Ptr CUInt
flags
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    CUInt
flags' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
flags
    let flags'' :: [RegionFlags]
flags'' = CUInt -> [RegionFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
flags'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
flags
    (Bool, [RegionFlags]) -> IO (Bool, [RegionFlags])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [RegionFlags]
flags'')

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterHasQregionMethodInfo
instance (signature ~ (Int32 -> Word32 -> m ((Bool, [Gtk.Flags.RegionFlags]))), MonadIO m) => O.MethodInfo WidgetPathIterHasQregionMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterHasQregion

#endif

-- method WidgetPath::iter_has_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to query, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "region name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RegionFlags" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the region flags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_has_region" gtk_widget_path_iter_has_region :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    Ptr CUInt ->                            -- flags : TInterface (Name {namespace = "Gtk", name = "RegionFlags"})
    IO CInt

{-# DEPRECATED widgetPathIterHasRegion ["(Since version 3.14)","The use of regions is deprecated."] #-}
-- | Returns 'P.True' if the widget at position /@pos@/ has the class /@name@/
-- defined, 'P.False' otherwise.
-- 
-- /Since: 3.0/
widgetPathIterHasRegion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to query, -1 for the path head
    -> T.Text
    -- ^ /@name@/: region name
    -> m ((Bool, [Gtk.Flags.RegionFlags]))
    -- ^ __Returns:__ 'P.True' if the class /@name@/ is defined for the widget at /@pos@/
widgetPathIterHasRegion :: WidgetPath -> Int32 -> Text -> m (Bool, [RegionFlags])
widgetPathIterHasRegion path :: WidgetPath
path pos :: Int32
pos name :: Text
name = IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags]))
-> IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags])
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr CUInt
flags <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    CInt
result <- Ptr WidgetPath -> Int32 -> CString -> Ptr CUInt -> IO CInt
gtk_widget_path_iter_has_region Ptr WidgetPath
path' Int32
pos CString
name' Ptr CUInt
flags
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    CUInt
flags' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
flags
    let flags'' :: [RegionFlags]
flags'' = CUInt -> [RegionFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
flags'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
flags
    (Bool, [RegionFlags]) -> IO (Bool, [RegionFlags])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [RegionFlags]
flags'')

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterHasRegionMethodInfo
instance (signature ~ (Int32 -> T.Text -> m ((Bool, [Gtk.Flags.RegionFlags]))), MonadIO m) => O.MethodInfo WidgetPathIterHasRegionMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterHasRegion

#endif

-- method WidgetPath::iter_list_classes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to query, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGSList (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_list_classes" gtk_widget_path_iter_list_classes :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO (Ptr (GSList CString))

-- | Returns a list with all the class names defined for the widget
-- at position /@pos@/ in the hierarchy defined in /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterListClasses ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to query, -1 for the path head
    -> m [T.Text]
    -- ^ __Returns:__ The list of
    --          classes, This is a list of strings, the t'GI.GLib.Structs.SList.SList' contents
    --          are owned by GTK+, but you should use @/g_slist_free()/@ to
    --          free the list itself.
widgetPathIterListClasses :: WidgetPath -> Int32 -> m [Text]
widgetPathIterListClasses path :: WidgetPath
path pos :: Int32
pos = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr (GSList CString)
result <- Ptr WidgetPath -> Int32 -> IO (Ptr (GSList CString))
gtk_widget_path_iter_list_classes Ptr WidgetPath
path' Int32
pos
    [CString]
result' <- Ptr (GSList CString) -> IO [CString]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList CString)
result
    [Text]
result'' <- (CString -> IO Text) -> [CString] -> IO [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [CString]
result'
    Ptr (GSList CString) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList CString)
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterListClassesMethodInfo
instance (signature ~ (Int32 -> m [T.Text]), MonadIO m) => O.MethodInfo WidgetPathIterListClassesMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterListClasses

#endif

-- method WidgetPath::iter_list_regions
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to query, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGSList (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_list_regions" gtk_widget_path_iter_list_regions :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    IO (Ptr (GSList CString))

{-# DEPRECATED widgetPathIterListRegions ["(Since version 3.14)","The use of regions is deprecated."] #-}
-- | Returns a list with all the region names defined for the widget
-- at position /@pos@/ in the hierarchy defined in /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterListRegions ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to query, -1 for the path head
    -> m [T.Text]
    -- ^ __Returns:__ The list of
    --          regions, This is a list of strings, the t'GI.GLib.Structs.SList.SList' contents
    --          are owned by GTK+, but you should use @/g_slist_free()/@ to
    --          free the list itself.
widgetPathIterListRegions :: WidgetPath -> Int32 -> m [Text]
widgetPathIterListRegions path :: WidgetPath
path pos :: Int32
pos = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr (GSList CString)
result <- Ptr WidgetPath -> Int32 -> IO (Ptr (GSList CString))
gtk_widget_path_iter_list_regions Ptr WidgetPath
path' Int32
pos
    [CString]
result' <- Ptr (GSList CString) -> IO [CString]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList CString)
result
    [Text]
result'' <- (CString -> IO Text) -> [CString] -> IO [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [CString]
result'
    Ptr (GSList CString) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList CString)
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterListRegionsMethodInfo
instance (signature ~ (Int32 -> m [T.Text]), MonadIO m) => O.MethodInfo WidgetPathIterListRegionsMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterListRegions

#endif

-- method WidgetPath::iter_remove_class
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "class name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_remove_class" gtk_widget_path_iter_remove_class :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Removes the class /@name@/ from the widget at position /@pos@/ in
-- the hierarchy defined in /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterRemoveClass ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> T.Text
    -- ^ /@name@/: class name
    -> m ()
widgetPathIterRemoveClass :: WidgetPath -> Int32 -> Text -> m ()
widgetPathIterRemoveClass path :: WidgetPath
path pos :: Int32
pos name :: Text
name = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr WidgetPath -> Int32 -> CString -> IO ()
gtk_widget_path_iter_remove_class Ptr WidgetPath
path' Int32
pos CString
name'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterRemoveClassMethodInfo
instance (signature ~ (Int32 -> T.Text -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterRemoveClassMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterRemoveClass

#endif

-- method WidgetPath::iter_remove_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "region name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_remove_region" gtk_widget_path_iter_remove_region :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    IO ()

{-# DEPRECATED widgetPathIterRemoveRegion ["(Since version 3.14)","The use of regions is deprecated."] #-}
-- | Removes the region /@name@/ from the widget at position /@pos@/ in
-- the hierarchy defined in /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterRemoveRegion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> T.Text
    -- ^ /@name@/: region name
    -> m ()
widgetPathIterRemoveRegion :: WidgetPath -> Int32 -> Text -> m ()
widgetPathIterRemoveRegion path :: WidgetPath
path pos :: Int32
pos name :: Text
name = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr WidgetPath -> Int32 -> CString -> IO ()
gtk_widget_path_iter_remove_region Ptr WidgetPath
path' Int32
pos CString
name'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterRemoveRegionMethodInfo
instance (signature ~ (Int32 -> T.Text -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterRemoveRegionMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterRemoveRegion

#endif

-- method WidgetPath::iter_set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "widget name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_set_name" gtk_widget_path_iter_set_name :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Sets the widget name for the widget found at position /@pos@/
-- in the widget hierarchy defined by /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterSetName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> T.Text
    -- ^ /@name@/: widget name
    -> m ()
widgetPathIterSetName :: WidgetPath -> Int32 -> Text -> m ()
widgetPathIterSetName path :: WidgetPath
path pos :: Int32
pos name :: Text
name = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr WidgetPath -> Int32 -> CString -> IO ()
gtk_widget_path_iter_set_name Ptr WidgetPath
path' Int32
pos CString
name'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterSetNameMethodInfo
instance (signature ~ (Int32 -> T.Text -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterSetNameMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterSetName

#endif

-- method WidgetPath::iter_set_object_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "object name to set or %NULL to unset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_set_object_name" gtk_widget_path_iter_set_object_name :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Sets the object name for a given position in the widget hierarchy
-- defined by /@path@/.
-- 
-- When set, the object name overrides the object type when matching
-- CSS.
-- 
-- /Since: 3.20/
widgetPathIterSetObjectName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> Maybe (T.Text)
    -- ^ /@name@/: object name to set or 'P.Nothing' to unset
    -> m ()
widgetPathIterSetObjectName :: WidgetPath -> Int32 -> Maybe Text -> m ()
widgetPathIterSetObjectName path :: WidgetPath
path pos :: Int32
pos name :: Maybe Text
name = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
maybeName <- case Maybe Text
name of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jName :: Text
jName -> do
            CString
jName' <- Text -> IO CString
textToCString Text
jName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jName'
    Ptr WidgetPath -> Int32 -> CString -> IO ()
gtk_widget_path_iter_set_object_name Ptr WidgetPath
path' Int32
pos CString
maybeName
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterSetObjectNameMethodInfo
instance (signature ~ (Int32 -> Maybe (T.Text) -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterSetObjectNameMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterSetObjectName

#endif

-- method WidgetPath::iter_set_object_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "object type to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_set_object_type" gtk_widget_path_iter_set_object_type :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CGType ->                               -- type : TBasicType TGType
    IO ()

-- | Sets the object type for a given position in the widget hierarchy
-- defined by /@path@/.
-- 
-- /Since: 3.0/
widgetPathIterSetObjectType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> GType
    -- ^ /@type@/: object type to set
    -> m ()
widgetPathIterSetObjectType :: WidgetPath -> Int32 -> GType -> m ()
widgetPathIterSetObjectType path :: WidgetPath
path pos :: Int32
pos type_ :: GType
type_ = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
    Ptr WidgetPath -> Int32 -> CGType -> IO ()
gtk_widget_path_iter_set_object_type Ptr WidgetPath
path' Int32
pos CGType
type_'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterSetObjectTypeMethodInfo
instance (signature ~ (Int32 -> GType -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterSetObjectTypeMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterSetObjectType

#endif

-- method WidgetPath::iter_set_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "position to modify, -1 for the path head"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StateFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "state flags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_iter_set_state" gtk_widget_path_iter_set_state :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    Int32 ->                                -- pos : TBasicType TInt
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    IO ()

-- | Sets the widget name for the widget found at position /@pos@/
-- in the widget hierarchy defined by /@path@/.
-- 
-- If you want to update just a single state flag, you need to do
-- this manually, as this function updates all state flags.
-- 
-- == Setting a flag
-- 
-- 
-- === /C code/
-- >
-- >gtk_widget_path_iter_set_state (path, pos, gtk_widget_path_iter_get_state (path, pos) | flag);
-- 
-- 
-- == Unsetting a flag
-- 
-- 
-- === /C code/
-- >
-- >gtk_widget_path_iter_set_state (path, pos, gtk_widget_path_iter_get_state (path, pos) & ~flag);
-- 
-- 
-- /Since: 3.14/
widgetPathIterSetState ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> Int32
    -- ^ /@pos@/: position to modify, -1 for the path head
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state flags
    -> m ()
widgetPathIterSetState :: WidgetPath -> Int32 -> [StateFlags] -> m ()
widgetPathIterSetState path :: WidgetPath
path pos :: Int32
pos state :: [StateFlags]
state = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr WidgetPath -> Int32 -> CUInt -> IO ()
gtk_widget_path_iter_set_state Ptr WidgetPath
path' Int32
pos CUInt
state'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathIterSetStateMethodInfo
instance (signature ~ (Int32 -> [Gtk.Flags.StateFlags] -> m ()), MonadIO m) => O.MethodInfo WidgetPathIterSetStateMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathIterSetState

#endif

-- method WidgetPath::length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_length" gtk_widget_path_length :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO Int32

-- | Returns the number of t'GI.Gtk.Objects.Widget.Widget' @/GTypes/@ between the represented
-- widget and its topmost container.
-- 
-- /Since: 3.0/
widgetPathLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> m Int32
    -- ^ __Returns:__ the number of elements in the path
widgetPathLength :: WidgetPath -> m Int32
widgetPathLength path :: WidgetPath
path = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Int32
result <- Ptr WidgetPath -> IO Int32
gtk_widget_path_length Ptr WidgetPath
path'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data WidgetPathLengthMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo WidgetPathLengthMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathLength

#endif

-- method WidgetPath::prepend_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "widget type to prepend"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_prepend_type" gtk_widget_path_prepend_type :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    CGType ->                               -- type : TBasicType TGType
    IO ()

-- | Prepends a widget type to the widget hierachy represented by /@path@/.
-- 
-- /Since: 3.0/
widgetPathPrependType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> GType
    -- ^ /@type@/: widget type to prepend
    -> m ()
widgetPathPrependType :: WidgetPath -> GType -> m ()
widgetPathPrependType path :: WidgetPath
path type_ :: GType
type_ = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
    Ptr WidgetPath -> CGType -> IO ()
gtk_widget_path_prepend_type Ptr WidgetPath
path' CGType
type_'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathPrependTypeMethodInfo
instance (signature ~ (GType -> m ()), MonadIO m) => O.MethodInfo WidgetPathPrependTypeMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathPrependType

#endif

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

foreign import ccall "gtk_widget_path_ref" gtk_widget_path_ref :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO (Ptr WidgetPath)

-- | Increments the reference count on /@path@/.
-- 
-- /Since: 3.2/
widgetPathRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> m WidgetPath
    -- ^ __Returns:__ /@path@/ itself.
widgetPathRef :: WidgetPath -> m WidgetPath
widgetPathRef path :: WidgetPath
path = IO WidgetPath -> m WidgetPath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WidgetPath -> m WidgetPath) -> IO WidgetPath -> m WidgetPath
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr WidgetPath
result <- Ptr WidgetPath -> IO (Ptr WidgetPath)
gtk_widget_path_ref Ptr WidgetPath
path'
    Text -> Ptr WidgetPath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "widgetPathRef" Ptr WidgetPath
result
    WidgetPath
result' <- ((ManagedPtr WidgetPath -> WidgetPath)
-> Ptr WidgetPath -> IO WidgetPath
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr WidgetPath -> WidgetPath
WidgetPath) Ptr WidgetPath
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    WidgetPath -> IO WidgetPath
forall (m :: * -> *) a. Monad m => a -> m a
return WidgetPath
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathRefMethodInfo
instance (signature ~ (m WidgetPath), MonadIO m) => O.MethodInfo WidgetPathRefMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathRef

#endif

-- method WidgetPath::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the path" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_to_string" gtk_widget_path_to_string :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO CString

-- | Dumps the widget path into a string representation. It tries to match
-- the CSS style as closely as possible (Note that there might be paths
-- that cannot be represented in CSS).
-- 
-- The main use of this code is for debugging purposes, so that you can
-- @/g_print()/@ the path or dump it in a gdb session.
-- 
-- /Since: 3.2/
widgetPathToString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: the path
    -> m T.Text
    -- ^ __Returns:__ A new string describing /@path@/.
widgetPathToString :: WidgetPath -> m Text
widgetPathToString path :: WidgetPath
path = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    CString
result <- Ptr WidgetPath -> IO CString
gtk_widget_path_to_string Ptr WidgetPath
path'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "widgetPathToString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data WidgetPathToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo WidgetPathToStringMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathToString

#endif

-- method WidgetPath::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWidgetPath" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_widget_path_unref" gtk_widget_path_unref :: 
    Ptr WidgetPath ->                       -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO ()

-- | Decrements the reference count on /@path@/, freeing the structure
-- if the reference count reaches 0.
-- 
-- /Since: 3.2/
widgetPathUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    WidgetPath
    -- ^ /@path@/: a t'GI.Gtk.Structs.WidgetPath.WidgetPath'
    -> m ()
widgetPathUnref :: WidgetPath -> m ()
widgetPathUnref path :: WidgetPath
path = 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 WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr WidgetPath -> IO ()
gtk_widget_path_unref Ptr WidgetPath
path'
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data WidgetPathUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo WidgetPathUnrefMethodInfo WidgetPath signature where
    overloadedMethod = widgetPathUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveWidgetPathMethod (t :: Symbol) (o :: *) :: * where
    ResolveWidgetPathMethod "appendForWidget" o = WidgetPathAppendForWidgetMethodInfo
    ResolveWidgetPathMethod "appendType" o = WidgetPathAppendTypeMethodInfo
    ResolveWidgetPathMethod "appendWithSiblings" o = WidgetPathAppendWithSiblingsMethodInfo
    ResolveWidgetPathMethod "copy" o = WidgetPathCopyMethodInfo
    ResolveWidgetPathMethod "free" o = WidgetPathFreeMethodInfo
    ResolveWidgetPathMethod "hasParent" o = WidgetPathHasParentMethodInfo
    ResolveWidgetPathMethod "isType" o = WidgetPathIsTypeMethodInfo
    ResolveWidgetPathMethod "iterAddClass" o = WidgetPathIterAddClassMethodInfo
    ResolveWidgetPathMethod "iterAddRegion" o = WidgetPathIterAddRegionMethodInfo
    ResolveWidgetPathMethod "iterClearClasses" o = WidgetPathIterClearClassesMethodInfo
    ResolveWidgetPathMethod "iterClearRegions" o = WidgetPathIterClearRegionsMethodInfo
    ResolveWidgetPathMethod "iterGetName" o = WidgetPathIterGetNameMethodInfo
    ResolveWidgetPathMethod "iterGetObjectName" o = WidgetPathIterGetObjectNameMethodInfo
    ResolveWidgetPathMethod "iterGetObjectType" o = WidgetPathIterGetObjectTypeMethodInfo
    ResolveWidgetPathMethod "iterGetSiblingIndex" o = WidgetPathIterGetSiblingIndexMethodInfo
    ResolveWidgetPathMethod "iterGetSiblings" o = WidgetPathIterGetSiblingsMethodInfo
    ResolveWidgetPathMethod "iterGetState" o = WidgetPathIterGetStateMethodInfo
    ResolveWidgetPathMethod "iterHasClass" o = WidgetPathIterHasClassMethodInfo
    ResolveWidgetPathMethod "iterHasName" o = WidgetPathIterHasNameMethodInfo
    ResolveWidgetPathMethod "iterHasQclass" o = WidgetPathIterHasQclassMethodInfo
    ResolveWidgetPathMethod "iterHasQname" o = WidgetPathIterHasQnameMethodInfo
    ResolveWidgetPathMethod "iterHasQregion" o = WidgetPathIterHasQregionMethodInfo
    ResolveWidgetPathMethod "iterHasRegion" o = WidgetPathIterHasRegionMethodInfo
    ResolveWidgetPathMethod "iterListClasses" o = WidgetPathIterListClassesMethodInfo
    ResolveWidgetPathMethod "iterListRegions" o = WidgetPathIterListRegionsMethodInfo
    ResolveWidgetPathMethod "iterRemoveClass" o = WidgetPathIterRemoveClassMethodInfo
    ResolveWidgetPathMethod "iterRemoveRegion" o = WidgetPathIterRemoveRegionMethodInfo
    ResolveWidgetPathMethod "iterSetName" o = WidgetPathIterSetNameMethodInfo
    ResolveWidgetPathMethod "iterSetObjectName" o = WidgetPathIterSetObjectNameMethodInfo
    ResolveWidgetPathMethod "iterSetObjectType" o = WidgetPathIterSetObjectTypeMethodInfo
    ResolveWidgetPathMethod "iterSetState" o = WidgetPathIterSetStateMethodInfo
    ResolveWidgetPathMethod "length" o = WidgetPathLengthMethodInfo
    ResolveWidgetPathMethod "prependType" o = WidgetPathPrependTypeMethodInfo
    ResolveWidgetPathMethod "ref" o = WidgetPathRefMethodInfo
    ResolveWidgetPathMethod "toString" o = WidgetPathToStringMethodInfo
    ResolveWidgetPathMethod "unref" o = WidgetPathUnrefMethodInfo
    ResolveWidgetPathMethod "getObjectType" o = WidgetPathGetObjectTypeMethodInfo
    ResolveWidgetPathMethod l o = O.MethodResolutionFailed l o

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

#endif