{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A GtkTreeRowReference tracks model changes so that it always refers to the
-- same row (a t'GI.Gtk.Structs.TreePath.TreePath' refers to a position, not a fixed row). Create a
-- new GtkTreeRowReference with 'GI.Gtk.Structs.TreeRowReference.treeRowReferenceNew'.

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

module GI.Gtk.Structs.TreeRowReference
    ( 

-- * Exported types
    TreeRowReference(..)                    ,
    noTreeRowReference                      ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveTreeRowReferenceMethod           ,
#endif


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    TreeRowReferenceCopyMethodInfo          ,
#endif
    treeRowReferenceCopy                    ,


-- ** deleted #method:deleted#

    treeRowReferenceDeleted                 ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    TreeRowReferenceFreeMethodInfo          ,
#endif
    treeRowReferenceFree                    ,


-- ** getModel #method:getModel#

#if defined(ENABLE_OVERLOADING)
    TreeRowReferenceGetModelMethodInfo      ,
#endif
    treeRowReferenceGetModel                ,


-- ** getPath #method:getPath#

#if defined(ENABLE_OVERLOADING)
    TreeRowReferenceGetPathMethodInfo       ,
#endif
    treeRowReferenceGetPath                 ,


-- ** inserted #method:inserted#

    treeRowReferenceInserted                ,


-- ** new #method:new#

    treeRowReferenceNew                     ,


-- ** newProxy #method:newProxy#

    treeRowReferenceNewProxy                ,


-- ** valid #method:valid#

#if defined(ENABLE_OVERLOADING)
    TreeRowReferenceValidMethodInfo         ,
#endif
    treeRowReferenceValid                   ,




    ) 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 qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeModel as Gtk.TreeModel
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreePath as Gtk.TreePath

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

instance BoxedObject TreeRowReference where
    boxedType :: TreeRowReference -> IO GType
boxedType _ = IO GType
c_gtk_tree_row_reference_get_type

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

-- | A convenience alias for `Nothing` :: `Maybe` `TreeRowReference`.
noTreeRowReference :: Maybe TreeRowReference
noTreeRowReference :: Maybe TreeRowReference
noTreeRowReference = Maybe TreeRowReference
forall a. Maybe a
Nothing


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

-- method TreeRowReference::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeModel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreeModel" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid #GtkTreePath-struct to monitor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "TreeRowReference" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_row_reference_new" gtk_tree_row_reference_new :: 
    Ptr Gtk.TreeModel.TreeModel ->          -- model : TInterface (Name {namespace = "Gtk", name = "TreeModel"})
    Ptr Gtk.TreePath.TreePath ->            -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO (Ptr TreeRowReference)

-- | Creates a row reference based on /@path@/.
-- 
-- This reference will keep pointing to the node pointed to
-- by /@path@/, so long as it exists. Any changes that occur on /@model@/ are
-- propagated, and the path is updated appropriately. If
-- /@path@/ isn’t a valid path in /@model@/, then 'P.Nothing' is returned.
treeRowReferenceNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.TreeModel.IsTreeModel a) =>
    a
    -- ^ /@model@/: a t'GI.Gtk.Interfaces.TreeModel.TreeModel'
    -> Gtk.TreePath.TreePath
    -- ^ /@path@/: a valid t'GI.Gtk.Structs.TreePath.TreePath'-struct to monitor
    -> m TreeRowReference
    -- ^ __Returns:__ a newly allocated t'GI.Gtk.Structs.TreeRowReference.TreeRowReference', or 'P.Nothing'
treeRowReferenceNew :: a -> TreePath -> m TreeRowReference
treeRowReferenceNew model :: a
model path :: TreePath
path = IO TreeRowReference -> m TreeRowReference
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeRowReference -> m TreeRowReference)
-> IO TreeRowReference -> m TreeRowReference
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreeModel
model' <- a -> IO (Ptr TreeModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreeRowReference
result <- Ptr TreeModel -> Ptr TreePath -> IO (Ptr TreeRowReference)
gtk_tree_row_reference_new Ptr TreeModel
model' Ptr TreePath
path'
    Text -> Ptr TreeRowReference -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "treeRowReferenceNew" Ptr TreeRowReference
result
    TreeRowReference
result' <- ((ManagedPtr TreeRowReference -> TreeRowReference)
-> Ptr TreeRowReference -> IO TreeRowReference
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeRowReference -> TreeRowReference
TreeRowReference) Ptr TreeRowReference
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
model
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    TreeRowReference -> IO TreeRowReference
forall (m :: * -> *) a. Monad m => a -> m a
return TreeRowReference
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method TreeRowReference::new_proxy
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a proxy #GObject" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "model"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeModel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreeModel" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid #GtkTreePath-struct to monitor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "TreeRowReference" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_row_reference_new_proxy" gtk_tree_row_reference_new_proxy :: 
    Ptr GObject.Object.Object ->            -- proxy : TInterface (Name {namespace = "GObject", name = "Object"})
    Ptr Gtk.TreeModel.TreeModel ->          -- model : TInterface (Name {namespace = "Gtk", name = "TreeModel"})
    Ptr Gtk.TreePath.TreePath ->            -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO (Ptr TreeRowReference)

-- | You do not need to use this function.
-- 
-- Creates a row reference based on /@path@/.
-- 
-- This reference will keep pointing to the node pointed to
-- by /@path@/, so long as it exists. If /@path@/ isn’t a valid
-- path in /@model@/, then 'P.Nothing' is returned. However, unlike
-- references created with 'GI.Gtk.Structs.TreeRowReference.treeRowReferenceNew', it
-- does not listen to the model for changes. The creator of
-- the row reference must do this explicitly using
-- 'GI.Gtk.Functions.treeRowReferenceInserted', 'GI.Gtk.Functions.treeRowReferenceDeleted',
-- @/gtk_tree_row_reference_reordered()/@.
-- 
-- These functions must be called exactly once per proxy when the
-- corresponding signal on the model is emitted. This single call
-- updates all row references for that proxy. Since built-in GTK+
-- objects like t'GI.Gtk.Objects.TreeView.TreeView' already use this mechanism internally,
-- using them as the proxy object will produce unpredictable results.
-- Further more, passing the same object as /@model@/ and /@proxy@/
-- doesn’t work for reasons of internal implementation.
-- 
-- This type of row reference is primarily meant by structures that
-- need to carefully monitor exactly when a row reference updates
-- itself, and is not generally needed by most applications.
treeRowReferenceNewProxy ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a, Gtk.TreeModel.IsTreeModel b) =>
    a
    -- ^ /@proxy@/: a proxy t'GI.GObject.Objects.Object.Object'
    -> b
    -- ^ /@model@/: a t'GI.Gtk.Interfaces.TreeModel.TreeModel'
    -> Gtk.TreePath.TreePath
    -- ^ /@path@/: a valid t'GI.Gtk.Structs.TreePath.TreePath'-struct to monitor
    -> m TreeRowReference
    -- ^ __Returns:__ a newly allocated t'GI.Gtk.Structs.TreeRowReference.TreeRowReference', or 'P.Nothing'
treeRowReferenceNewProxy :: a -> b -> TreePath -> m TreeRowReference
treeRowReferenceNewProxy proxy :: a
proxy model :: b
model path :: TreePath
path = IO TreeRowReference -> m TreeRowReference
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeRowReference -> m TreeRowReference)
-> IO TreeRowReference -> m TreeRowReference
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
proxy' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr TreeModel
model' <- b -> IO (Ptr TreeModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
model
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr TreeRowReference
result <- Ptr Object
-> Ptr TreeModel -> Ptr TreePath -> IO (Ptr TreeRowReference)
gtk_tree_row_reference_new_proxy Ptr Object
proxy' Ptr TreeModel
model' Ptr TreePath
path'
    Text -> Ptr TreeRowReference -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "treeRowReferenceNewProxy" Ptr TreeRowReference
result
    TreeRowReference
result' <- ((ManagedPtr TreeRowReference -> TreeRowReference)
-> Ptr TreeRowReference -> IO TreeRowReference
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeRowReference -> TreeRowReference
TreeRowReference) Ptr TreeRowReference
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
model
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    TreeRowReference -> IO TreeRowReference
forall (m :: * -> *) a. Monad m => a -> m a
return TreeRowReference
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_tree_row_reference_copy" gtk_tree_row_reference_copy :: 
    Ptr TreeRowReference ->                 -- reference : TInterface (Name {namespace = "Gtk", name = "TreeRowReference"})
    IO (Ptr TreeRowReference)

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

#if defined(ENABLE_OVERLOADING)
data TreeRowReferenceCopyMethodInfo
instance (signature ~ (m TreeRowReference), MonadIO m) => O.MethodInfo TreeRowReferenceCopyMethodInfo TreeRowReference signature where
    overloadedMethod = treeRowReferenceCopy

#endif

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

foreign import ccall "gtk_tree_row_reference_free" gtk_tree_row_reference_free :: 
    Ptr TreeRowReference ->                 -- reference : TInterface (Name {namespace = "Gtk", name = "TreeRowReference"})
    IO ()

-- | Free’s /@reference@/. /@reference@/ may be 'P.Nothing'
treeRowReferenceFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreeRowReference
    -- ^ /@reference@/: a t'GI.Gtk.Structs.TreeRowReference.TreeRowReference', or 'P.Nothing'
    -> m ()
treeRowReferenceFree :: TreeRowReference -> m ()
treeRowReferenceFree reference :: TreeRowReference
reference = 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 TreeRowReference
reference' <- TreeRowReference -> IO (Ptr TreeRowReference)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeRowReference
reference
    Ptr TreeRowReference -> IO ()
gtk_tree_row_reference_free Ptr TreeRowReference
reference'
    TreeRowReference -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeRowReference
reference
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TreeRowReferenceFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TreeRowReferenceFreeMethodInfo TreeRowReference signature where
    overloadedMethod = treeRowReferenceFree

#endif

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

foreign import ccall "gtk_tree_row_reference_get_model" gtk_tree_row_reference_get_model :: 
    Ptr TreeRowReference ->                 -- reference : TInterface (Name {namespace = "Gtk", name = "TreeRowReference"})
    IO (Ptr Gtk.TreeModel.TreeModel)

-- | Returns the model that the row reference is monitoring.
-- 
-- /Since: 2.8/
treeRowReferenceGetModel ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreeRowReference
    -- ^ /@reference@/: a t'GI.Gtk.Structs.TreeRowReference.TreeRowReference'
    -> m Gtk.TreeModel.TreeModel
    -- ^ __Returns:__ the model
treeRowReferenceGetModel :: TreeRowReference -> m TreeModel
treeRowReferenceGetModel reference :: TreeRowReference
reference = IO TreeModel -> m TreeModel
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeModel -> m TreeModel) -> IO TreeModel -> m TreeModel
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreeRowReference
reference' <- TreeRowReference -> IO (Ptr TreeRowReference)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeRowReference
reference
    Ptr TreeModel
result <- Ptr TreeRowReference -> IO (Ptr TreeModel)
gtk_tree_row_reference_get_model Ptr TreeRowReference
reference'
    Text -> Ptr TreeModel -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "treeRowReferenceGetModel" Ptr TreeModel
result
    TreeModel
result' <- ((ManagedPtr TreeModel -> TreeModel)
-> Ptr TreeModel -> IO TreeModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TreeModel -> TreeModel
Gtk.TreeModel.TreeModel) Ptr TreeModel
result
    TreeRowReference -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeRowReference
reference
    TreeModel -> IO TreeModel
forall (m :: * -> *) a. Monad m => a -> m a
return TreeModel
result'

#if defined(ENABLE_OVERLOADING)
data TreeRowReferenceGetModelMethodInfo
instance (signature ~ (m Gtk.TreeModel.TreeModel), MonadIO m) => O.MethodInfo TreeRowReferenceGetModelMethodInfo TreeRowReference signature where
    overloadedMethod = treeRowReferenceGetModel

#endif

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

foreign import ccall "gtk_tree_row_reference_get_path" gtk_tree_row_reference_get_path :: 
    Ptr TreeRowReference ->                 -- reference : TInterface (Name {namespace = "Gtk", name = "TreeRowReference"})
    IO (Ptr Gtk.TreePath.TreePath)

-- | Returns a path that the row reference currently points to,
-- or 'P.Nothing' if the path pointed to is no longer valid.
treeRowReferenceGetPath ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreeRowReference
    -- ^ /@reference@/: a t'GI.Gtk.Structs.TreeRowReference.TreeRowReference'
    -> m (Maybe Gtk.TreePath.TreePath)
    -- ^ __Returns:__ a current path, or 'P.Nothing'
treeRowReferenceGetPath :: TreeRowReference -> m (Maybe TreePath)
treeRowReferenceGetPath reference :: TreeRowReference
reference = IO (Maybe TreePath) -> m (Maybe TreePath)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TreePath) -> m (Maybe TreePath))
-> IO (Maybe TreePath) -> m (Maybe TreePath)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TreeRowReference
reference' <- TreeRowReference -> IO (Ptr TreeRowReference)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeRowReference
reference
    Ptr TreePath
result <- Ptr TreeRowReference -> IO (Ptr TreePath)
gtk_tree_row_reference_get_path Ptr TreeRowReference
reference'
    Maybe TreePath
maybeResult <- Ptr TreePath
-> (Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TreePath
result ((Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath))
-> (Ptr TreePath -> IO TreePath) -> IO (Maybe TreePath)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr TreePath
result' -> do
        TreePath
result'' <- ((ManagedPtr TreePath -> TreePath) -> Ptr TreePath -> IO TreePath
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreePath -> TreePath
Gtk.TreePath.TreePath) Ptr TreePath
result'
        TreePath -> IO TreePath
forall (m :: * -> *) a. Monad m => a -> m a
return TreePath
result''
    TreeRowReference -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeRowReference
reference
    Maybe TreePath -> IO (Maybe TreePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TreePath
maybeResult

#if defined(ENABLE_OVERLOADING)
data TreeRowReferenceGetPathMethodInfo
instance (signature ~ (m (Maybe Gtk.TreePath.TreePath)), MonadIO m) => O.MethodInfo TreeRowReferenceGetPathMethodInfo TreeRowReference signature where
    overloadedMethod = treeRowReferenceGetPath

#endif

-- method TreeRowReference::valid
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "reference"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeRowReference" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTreeRowReference, or %NULL"
--                 , 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_tree_row_reference_valid" gtk_tree_row_reference_valid :: 
    Ptr TreeRowReference ->                 -- reference : TInterface (Name {namespace = "Gtk", name = "TreeRowReference"})
    IO CInt

-- | Returns 'P.True' if the /@reference@/ is non-'P.Nothing' and refers to
-- a current valid path.
treeRowReferenceValid ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TreeRowReference
    -- ^ /@reference@/: a t'GI.Gtk.Structs.TreeRowReference.TreeRowReference', or 'P.Nothing'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@reference@/ points to a valid path
treeRowReferenceValid :: TreeRowReference -> m Bool
treeRowReferenceValid reference :: TreeRowReference
reference = 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 TreeRowReference
reference' <- TreeRowReference -> IO (Ptr TreeRowReference)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeRowReference
reference
    CInt
result <- Ptr TreeRowReference -> IO CInt
gtk_tree_row_reference_valid Ptr TreeRowReference
reference'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    TreeRowReference -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeRowReference
reference
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TreeRowReferenceValidMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TreeRowReferenceValidMethodInfo TreeRowReference signature where
    overloadedMethod = treeRowReferenceValid

#endif

-- method TreeRowReference::deleted
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GObject" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the path position that was deleted"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_row_reference_deleted" gtk_tree_row_reference_deleted :: 
    Ptr GObject.Object.Object ->            -- proxy : TInterface (Name {namespace = "GObject", name = "Object"})
    Ptr Gtk.TreePath.TreePath ->            -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO ()

-- | Lets a set of row reference created by
-- 'GI.Gtk.Structs.TreeRowReference.treeRowReferenceNewProxy' know that the
-- model emitted the [rowDeleted]("GI.Gtk.Interfaces.TreeModel#signal:rowDeleted") signal.
treeRowReferenceDeleted ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) =>
    a
    -- ^ /@proxy@/: a t'GI.GObject.Objects.Object.Object'
    -> Gtk.TreePath.TreePath
    -- ^ /@path@/: the path position that was deleted
    -> m ()
treeRowReferenceDeleted :: a -> TreePath -> m ()
treeRowReferenceDeleted proxy :: a
proxy path :: TreePath
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 Object
proxy' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr Object -> Ptr TreePath -> IO ()
gtk_tree_row_reference_deleted Ptr Object
proxy' Ptr TreePath
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method TreeRowReference::inserted
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "proxy"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GObject" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreePath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the row position that was inserted"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_tree_row_reference_inserted" gtk_tree_row_reference_inserted :: 
    Ptr GObject.Object.Object ->            -- proxy : TInterface (Name {namespace = "GObject", name = "Object"})
    Ptr Gtk.TreePath.TreePath ->            -- path : TInterface (Name {namespace = "Gtk", name = "TreePath"})
    IO ()

-- | Lets a set of row reference created by
-- 'GI.Gtk.Structs.TreeRowReference.treeRowReferenceNewProxy' know that the
-- model emitted the [rowInserted]("GI.Gtk.Interfaces.TreeModel#signal:rowInserted") signal.
treeRowReferenceInserted ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) =>
    a
    -- ^ /@proxy@/: a t'GI.GObject.Objects.Object.Object'
    -> Gtk.TreePath.TreePath
    -- ^ /@path@/: the row position that was inserted
    -> m ()
treeRowReferenceInserted :: a -> TreePath -> m ()
treeRowReferenceInserted proxy :: a
proxy path :: TreePath
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 Object
proxy' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
proxy
    Ptr TreePath
path' <- TreePath -> IO (Ptr TreePath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreePath
path
    Ptr Object -> Ptr TreePath -> IO ()
gtk_tree_row_reference_inserted Ptr Object
proxy' Ptr TreePath
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
proxy
    TreePath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreePath
path
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTreeRowReferenceMethod (t :: Symbol) (o :: *) :: * where
    ResolveTreeRowReferenceMethod "copy" o = TreeRowReferenceCopyMethodInfo
    ResolveTreeRowReferenceMethod "free" o = TreeRowReferenceFreeMethodInfo
    ResolveTreeRowReferenceMethod "valid" o = TreeRowReferenceValidMethodInfo
    ResolveTreeRowReferenceMethod "getModel" o = TreeRowReferenceGetModelMethodInfo
    ResolveTreeRowReferenceMethod "getPath" o = TreeRowReferenceGetPathMethodInfo
    ResolveTreeRowReferenceMethod l o = O.MethodResolutionFailed l o

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

#endif