{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.ListStore
    ( 
    ListStore(..)                           ,
    IsListStore                             ,
    toListStore                             ,
    noListStore                             ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveListStoreMethod                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    ListStoreAppendMethodInfo               ,
#endif
    listStoreAppend                         ,
#if defined(ENABLE_OVERLOADING)
    ListStoreInsertMethodInfo               ,
#endif
    listStoreInsert                         ,
#if defined(ENABLE_OVERLOADING)
    ListStoreInsertSortedMethodInfo         ,
#endif
    listStoreInsertSorted                   ,
    listStoreNew                            ,
#if defined(ENABLE_OVERLOADING)
    ListStoreRemoveMethodInfo               ,
#endif
    listStoreRemove                         ,
#if defined(ENABLE_OVERLOADING)
    ListStoreRemoveAllMethodInfo            ,
#endif
    listStoreRemoveAll                      ,
#if defined(ENABLE_OVERLOADING)
    ListStoreSortMethodInfo                 ,
#endif
    listStoreSort                           ,
#if defined(ENABLE_OVERLOADING)
    ListStoreSpliceMethodInfo               ,
#endif
    listStoreSplice                         ,
 
#if defined(ENABLE_OVERLOADING)
    ListStoreItemTypePropertyInfo           ,
#endif
    constructListStoreItemType              ,
    getListStoreItemType                    ,
#if defined(ENABLE_OVERLOADING)
    listStoreItemType                       ,
#endif
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.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 Control.Monad.IO.Class as MIO
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.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
newtype ListStore = ListStore (ManagedPtr ListStore)
    deriving (ListStore -> ListStore -> Bool
(ListStore -> ListStore -> Bool)
-> (ListStore -> ListStore -> Bool) -> Eq ListStore
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStore -> ListStore -> Bool
$c/= :: ListStore -> ListStore -> Bool
== :: ListStore -> ListStore -> Bool
$c== :: ListStore -> ListStore -> Bool
Eq)
foreign import ccall "g_list_store_get_type"
    c_g_list_store_get_type :: IO GType
instance GObject ListStore where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_list_store_get_type
    
instance B.GValue.IsGValue ListStore where
    toGValue :: ListStore -> IO GValue
toGValue o :: ListStore
o = do
        GType
gtype <- IO GType
c_g_list_store_get_type
        ListStore -> (Ptr ListStore -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ListStore
o (GType
-> (GValue -> Ptr ListStore -> IO ()) -> Ptr ListStore -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ListStore -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO ListStore
fromGValue gv :: GValue
gv = do
        Ptr ListStore
ptr <- GValue -> IO (Ptr ListStore)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ListStore)
        (ManagedPtr ListStore -> ListStore)
-> Ptr ListStore -> IO ListStore
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ListStore -> ListStore
ListStore Ptr ListStore
ptr
        
    
class (GObject o, O.IsDescendantOf ListStore o) => IsListStore o
instance (GObject o, O.IsDescendantOf ListStore o) => IsListStore o
instance O.HasParentTypes ListStore
type instance O.ParentTypes ListStore = '[GObject.Object.Object, Gio.ListModel.ListModel]
toListStore :: (MonadIO m, IsListStore o) => o -> m ListStore
toListStore :: o -> m ListStore
toListStore = IO ListStore -> m ListStore
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ListStore -> m ListStore)
-> (o -> IO ListStore) -> o -> m ListStore
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ListStore -> ListStore) -> o -> IO ListStore
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ListStore -> ListStore
ListStore
noListStore :: Maybe ListStore
noListStore :: Maybe ListStore
noListStore = Maybe ListStore
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveListStoreMethod (t :: Symbol) (o :: *) :: * where
    ResolveListStoreMethod "append" o = ListStoreAppendMethodInfo
    ResolveListStoreMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveListStoreMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveListStoreMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveListStoreMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveListStoreMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveListStoreMethod "insert" o = ListStoreInsertMethodInfo
    ResolveListStoreMethod "insertSorted" o = ListStoreInsertSortedMethodInfo
    ResolveListStoreMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveListStoreMethod "itemsChanged" o = Gio.ListModel.ListModelItemsChangedMethodInfo
    ResolveListStoreMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveListStoreMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveListStoreMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveListStoreMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveListStoreMethod "remove" o = ListStoreRemoveMethodInfo
    ResolveListStoreMethod "removeAll" o = ListStoreRemoveAllMethodInfo
    ResolveListStoreMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveListStoreMethod "sort" o = ListStoreSortMethodInfo
    ResolveListStoreMethod "splice" o = ListStoreSpliceMethodInfo
    ResolveListStoreMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveListStoreMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveListStoreMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveListStoreMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveListStoreMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveListStoreMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveListStoreMethod "getItem" o = Gio.ListModel.ListModelGetItemMethodInfo
    ResolveListStoreMethod "getItemType" o = Gio.ListModel.ListModelGetItemTypeMethodInfo
    ResolveListStoreMethod "getNItems" o = Gio.ListModel.ListModelGetNItemsMethodInfo
    ResolveListStoreMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveListStoreMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveListStoreMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveListStoreMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveListStoreMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveListStoreMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveListStoreMethod t ListStore, O.MethodInfo info ListStore p) => OL.IsLabel t (ListStore -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#endif
   
   
   
getListStoreItemType :: (MonadIO m, IsListStore o) => o -> m GType
getListStoreItemType :: o -> m GType
getListStoreItemType obj :: o
obj = 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
$ o -> String -> IO GType
forall a. GObject a => a -> String -> IO GType
B.Properties.getObjectPropertyGType o
obj "item-type"
constructListStoreItemType :: (IsListStore o, MIO.MonadIO m) => GType -> m (GValueConstruct o)
constructListStoreItemType :: GType -> m (GValueConstruct o)
constructListStoreItemType val :: GType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> GType -> IO (GValueConstruct o)
forall o. String -> GType -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyGType "item-type" GType
val
#if defined(ENABLE_OVERLOADING)
data ListStoreItemTypePropertyInfo
instance AttrInfo ListStoreItemTypePropertyInfo where
    type AttrAllowedOps ListStoreItemTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ListStoreItemTypePropertyInfo = IsListStore
    type AttrSetTypeConstraint ListStoreItemTypePropertyInfo = (~) GType
    type AttrTransferTypeConstraint ListStoreItemTypePropertyInfo = (~) GType
    type AttrTransferType ListStoreItemTypePropertyInfo = GType
    type AttrGetType ListStoreItemTypePropertyInfo = GType
    type AttrLabel ListStoreItemTypePropertyInfo = "item-type"
    type AttrOrigin ListStoreItemTypePropertyInfo = ListStore
    attrGet = getListStoreItemType
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructListStoreItemType
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ListStore
type instance O.AttributeList ListStore = ListStoreAttributeList
type ListStoreAttributeList = ('[ '("itemType", ListStoreItemTypePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
listStoreItemType :: AttrLabelProxy "itemType"
listStoreItemType = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ListStore = ListStoreSignalList
type ListStoreSignalList = ('[ '("itemsChanged", Gio.ListModel.ListModelItemsChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_list_store_new" g_list_store_new :: 
    CGType ->                               
    IO (Ptr ListStore)
listStoreNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GType
    
    -> m ListStore
    
listStoreNew :: GType -> m ListStore
listStoreNew itemType :: GType
itemType = IO ListStore -> m ListStore
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ListStore -> m ListStore) -> IO ListStore -> m ListStore
forall a b. (a -> b) -> a -> b
$ do
    let itemType' :: CGType
itemType' = GType -> CGType
gtypeToCGType GType
itemType
    Ptr ListStore
result <- CGType -> IO (Ptr ListStore)
g_list_store_new CGType
itemType'
    Text -> Ptr ListStore -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "listStoreNew" Ptr ListStore
result
    ListStore
result' <- ((ManagedPtr ListStore -> ListStore)
-> Ptr ListStore -> IO ListStore
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ListStore -> ListStore
ListStore) Ptr ListStore
result
    ListStore -> IO ListStore
forall (m :: * -> *) a. Monad m => a -> m a
return ListStore
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_list_store_append" g_list_store_append :: 
    Ptr ListStore ->                        
    Ptr GObject.Object.Object ->            
    IO ()
listStoreAppend ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a, GObject.Object.IsObject b) =>
    a
    
    -> b
    
    -> m ()
listStoreAppend :: a -> b -> m ()
listStoreAppend store :: a
store item :: b
item = 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 ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr Object
item' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    Ptr ListStore -> Ptr Object -> IO ()
g_list_store_append Ptr ListStore
store' Ptr Object
item'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ListStoreAppendMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsListStore a, GObject.Object.IsObject b) => O.MethodInfo ListStoreAppendMethodInfo a signature where
    overloadedMethod = listStoreAppend
#endif
foreign import ccall "g_list_store_insert" g_list_store_insert :: 
    Ptr ListStore ->                        
    Word32 ->                               
    Ptr GObject.Object.Object ->            
    IO ()
listStoreInsert ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a, GObject.Object.IsObject b) =>
    a
    
    -> Word32
    
    -> b
    
    -> m ()
listStoreInsert :: a -> Word32 -> b -> m ()
listStoreInsert store :: a
store position :: Word32
position item :: b
item = 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 ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr Object
item' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    Ptr ListStore -> Word32 -> Ptr Object -> IO ()
g_list_store_insert Ptr ListStore
store' Word32
position Ptr Object
item'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ListStoreInsertMethodInfo
instance (signature ~ (Word32 -> b -> m ()), MonadIO m, IsListStore a, GObject.Object.IsObject b) => O.MethodInfo ListStoreInsertMethodInfo a signature where
    overloadedMethod = listStoreInsert
#endif
foreign import ccall "g_list_store_insert_sorted" g_list_store_insert_sorted :: 
    Ptr ListStore ->                        
    Ptr GObject.Object.Object ->            
    FunPtr GLib.Callbacks.C_CompareDataFunc -> 
    Ptr () ->                               
    IO Word32
listStoreInsertSorted ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a, GObject.Object.IsObject b) =>
    a
    
    -> b
    
    -> GLib.Callbacks.CompareDataFunc
    
    -> m Word32
    
listStoreInsertSorted :: a -> b -> CompareDataFunc -> m Word32
listStoreInsertSorted store :: a
store item :: b
item compareFunc :: CompareDataFunc
compareFunc = 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 ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr Object
item' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
item
    FunPtr C_CompareDataFunc
compareFunc' <- C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc)
GLib.Callbacks.mk_CompareDataFunc (Maybe (Ptr (FunPtr C_CompareDataFunc))
-> C_CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.wrap_CompareDataFunc Maybe (Ptr (FunPtr C_CompareDataFunc))
forall a. Maybe a
Nothing (CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.drop_closures_CompareDataFunc CompareDataFunc
compareFunc))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Word32
result <- Ptr ListStore
-> Ptr Object -> FunPtr C_CompareDataFunc -> Ptr () -> IO Word32
g_list_store_insert_sorted Ptr ListStore
store' Ptr Object
item' FunPtr C_CompareDataFunc
compareFunc' Ptr ()
forall a. Ptr a
userData
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_CompareDataFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_CompareDataFunc
compareFunc'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
item
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data ListStoreInsertSortedMethodInfo
instance (signature ~ (b -> GLib.Callbacks.CompareDataFunc -> m Word32), MonadIO m, IsListStore a, GObject.Object.IsObject b) => O.MethodInfo ListStoreInsertSortedMethodInfo a signature where
    overloadedMethod = listStoreInsertSorted
#endif
foreign import ccall "g_list_store_remove" g_list_store_remove :: 
    Ptr ListStore ->                        
    Word32 ->                               
    IO ()
listStoreRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    
    -> Word32
    
    -> m ()
listStoreRemove :: a -> Word32 -> m ()
listStoreRemove store :: a
store position :: Word32
position = 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 ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr ListStore -> Word32 -> IO ()
g_list_store_remove Ptr ListStore
store' Word32
position
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ListStoreRemoveMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreRemoveMethodInfo a signature where
    overloadedMethod = listStoreRemove
#endif
foreign import ccall "g_list_store_remove_all" g_list_store_remove_all :: 
    Ptr ListStore ->                        
    IO ()
listStoreRemoveAll ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    
    -> m ()
listStoreRemoveAll :: a -> m ()
listStoreRemoveAll store :: a
store = 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 ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr ListStore -> IO ()
g_list_store_remove_all Ptr ListStore
store'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ListStoreRemoveAllMethodInfo
instance (signature ~ (m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreRemoveAllMethodInfo a signature where
    overloadedMethod = listStoreRemoveAll
#endif
foreign import ccall "g_list_store_sort" g_list_store_sort :: 
    Ptr ListStore ->                        
    FunPtr GLib.Callbacks.C_CompareDataFunc -> 
    Ptr () ->                               
    IO ()
listStoreSort ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    
    -> GLib.Callbacks.CompareDataFunc
    
    -> m ()
listStoreSort :: a -> CompareDataFunc -> m ()
listStoreSort store :: a
store compareFunc :: CompareDataFunc
compareFunc = 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 ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    FunPtr C_CompareDataFunc
compareFunc' <- C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc)
GLib.Callbacks.mk_CompareDataFunc (Maybe (Ptr (FunPtr C_CompareDataFunc))
-> C_CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.wrap_CompareDataFunc Maybe (Ptr (FunPtr C_CompareDataFunc))
forall a. Maybe a
Nothing (CompareDataFunc -> C_CompareDataFunc
GLib.Callbacks.drop_closures_CompareDataFunc CompareDataFunc
compareFunc))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr ListStore -> FunPtr C_CompareDataFunc -> Ptr () -> IO ()
g_list_store_sort Ptr ListStore
store' FunPtr C_CompareDataFunc
compareFunc' Ptr ()
forall a. Ptr a
userData
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_CompareDataFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_CompareDataFunc
compareFunc'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ListStoreSortMethodInfo
instance (signature ~ (GLib.Callbacks.CompareDataFunc -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreSortMethodInfo a signature where
    overloadedMethod = listStoreSort
#endif
foreign import ccall "g_list_store_splice" g_list_store_splice :: 
    Ptr ListStore ->                        
    Word32 ->                               
    Word32 ->                               
    Ptr (Ptr GObject.Object.Object) ->      
    Word32 ->                               
    IO ()
listStoreSplice ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    
    -> Word32
    
    -> Word32
    
    -> [GObject.Object.Object]
    
    -> m ()
listStoreSplice :: a -> Word32 -> Word32 -> [Object] -> m ()
listStoreSplice store :: a
store position :: Word32
position nRemovals :: Word32
nRemovals additions :: [Object]
additions = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let nAdditions :: Word32
nAdditions = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Object] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Object]
additions
    Ptr ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    [Ptr Object]
additions' <- (Object -> IO (Ptr Object)) -> [Object] -> IO [Ptr Object]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Object -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [Object]
additions
    Ptr (Ptr Object)
additions'' <- [Ptr Object] -> IO (Ptr (Ptr Object))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packPtrArray [Ptr Object]
additions'
    Ptr ListStore
-> Word32 -> Word32 -> Ptr (Ptr Object) -> Word32 -> IO ()
g_list_store_splice Ptr ListStore
store' Word32
position Word32
nRemovals Ptr (Ptr Object)
additions'' Word32
nAdditions
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    (Object -> IO ()) -> [Object] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Object -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Object]
additions
    Ptr (Ptr Object) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Object)
additions''
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ListStoreSpliceMethodInfo
instance (signature ~ (Word32 -> Word32 -> [GObject.Object.Object] -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreSpliceMethodInfo a signature where
    overloadedMethod = listStoreSplice
#endif