{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Dazzle.Objects.GraphModel
    ( 

-- * Exported types
    GraphModel(..)                          ,
    IsGraphModel                            ,
    toGraphModel                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addColumn]("GI.Dazzle.Objects.GraphModel#g:method:addColumn"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [push]("GI.Dazzle.Objects.GraphModel#g:method:push"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getEndTime]("GI.Dazzle.Objects.GraphModel#g:method:getEndTime"), [getIterFirst]("GI.Dazzle.Objects.GraphModel#g:method:getIterFirst"), [getIterLast]("GI.Dazzle.Objects.GraphModel#g:method:getIterLast"), [getMaxSamples]("GI.Dazzle.Objects.GraphModel#g:method:getMaxSamples"), [getNColumns]("GI.Dazzle.Objects.GraphModel#g:method:getNColumns"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTimespan]("GI.Dazzle.Objects.GraphModel#g:method:getTimespan").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setMaxSamples]("GI.Dazzle.Objects.GraphModel#g:method:setMaxSamples"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTimespan]("GI.Dazzle.Objects.GraphModel#g:method:setTimespan").

#if defined(ENABLE_OVERLOADING)
    ResolveGraphModelMethod                 ,
#endif

-- ** addColumn #method:addColumn#

#if defined(ENABLE_OVERLOADING)
    GraphModelAddColumnMethodInfo           ,
#endif
    graphModelAddColumn                     ,


-- ** getEndTime #method:getEndTime#

#if defined(ENABLE_OVERLOADING)
    GraphModelGetEndTimeMethodInfo          ,
#endif
    graphModelGetEndTime                    ,


-- ** getIterFirst #method:getIterFirst#

#if defined(ENABLE_OVERLOADING)
    GraphModelGetIterFirstMethodInfo        ,
#endif
    graphModelGetIterFirst                  ,


-- ** getIterLast #method:getIterLast#

#if defined(ENABLE_OVERLOADING)
    GraphModelGetIterLastMethodInfo         ,
#endif
    graphModelGetIterLast                   ,


-- ** getMaxSamples #method:getMaxSamples#

#if defined(ENABLE_OVERLOADING)
    GraphModelGetMaxSamplesMethodInfo       ,
#endif
    graphModelGetMaxSamples                 ,


-- ** getNColumns #method:getNColumns#

#if defined(ENABLE_OVERLOADING)
    GraphModelGetNColumnsMethodInfo         ,
#endif
    graphModelGetNColumns                   ,


-- ** getTimespan #method:getTimespan#

#if defined(ENABLE_OVERLOADING)
    GraphModelGetTimespanMethodInfo         ,
#endif
    graphModelGetTimespan                   ,


-- ** iterGetTimestamp #method:iterGetTimestamp#

    graphModelIterGetTimestamp              ,


-- ** iterGetValue #method:iterGetValue#

    graphModelIterGetValue                  ,


-- ** iterNext #method:iterNext#

    graphModelIterNext                      ,


-- ** iterSet #method:iterSet#

    graphModelIterSet                       ,


-- ** new #method:new#

    graphModelNew                           ,


-- ** push #method:push#

#if defined(ENABLE_OVERLOADING)
    GraphModelPushMethodInfo                ,
#endif
    graphModelPush                          ,


-- ** setMaxSamples #method:setMaxSamples#

#if defined(ENABLE_OVERLOADING)
    GraphModelSetMaxSamplesMethodInfo       ,
#endif
    graphModelSetMaxSamples                 ,


-- ** setTimespan #method:setTimespan#

#if defined(ENABLE_OVERLOADING)
    GraphModelSetTimespanMethodInfo         ,
#endif
    graphModelSetTimespan                   ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    GraphModelMaxSamplesPropertyInfo        ,
#endif
    constructGraphModelMaxSamples           ,
    getGraphModelMaxSamples                 ,
#if defined(ENABLE_OVERLOADING)
    graphModelMaxSamples                    ,
#endif
    setGraphModelMaxSamples                 ,


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

#if defined(ENABLE_OVERLOADING)
    GraphModelTimespanPropertyInfo          ,
#endif
    constructGraphModelTimespan             ,
    getGraphModelTimespan                   ,
#if defined(ENABLE_OVERLOADING)
    graphModelTimespan                      ,
#endif
    setGraphModelTimespan                   ,


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

#if defined(ENABLE_OVERLOADING)
    GraphModelValueMaxPropertyInfo          ,
#endif
    constructGraphModelValueMax             ,
    getGraphModelValueMax                   ,
#if defined(ENABLE_OVERLOADING)
    graphModelValueMax                      ,
#endif
    setGraphModelValueMax                   ,


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

#if defined(ENABLE_OVERLOADING)
    GraphModelValueMinPropertyInfo          ,
#endif
    constructGraphModelValueMin             ,
    getGraphModelValueMin                   ,
#if defined(ENABLE_OVERLOADING)
    graphModelValueMin                      ,
#endif
    setGraphModelValueMin                   ,




 -- * Signals


-- ** changed #signal:changed#

    GraphModelChangedCallback               ,
#if defined(ENABLE_OVERLOADING)
    GraphModelChangedSignalInfo             ,
#endif
    afterGraphModelChanged                  ,
    onGraphModelChanged                     ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import {-# SOURCE #-} qualified GI.Dazzle.Objects.GraphColumn as Dazzle.GraphColumn
import {-# SOURCE #-} qualified GI.Dazzle.Structs.GraphModelIter as Dazzle.GraphModelIter
import qualified GI.GObject.Objects.Object as GObject.Object

#else
import {-# SOURCE #-} qualified GI.Dazzle.Objects.GraphColumn as Dazzle.GraphColumn
import {-# SOURCE #-} qualified GI.Dazzle.Structs.GraphModelIter as Dazzle.GraphModelIter
import qualified GI.GObject.Objects.Object as GObject.Object

#endif

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

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

foreign import ccall "dzl_graph_view_model_get_type"
    c_dzl_graph_view_model_get_type :: IO B.Types.GType

instance B.Types.TypedObject GraphModel where
    glibType :: IO GType
glibType = IO GType
c_dzl_graph_view_model_get_type

instance B.Types.GObject GraphModel

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

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

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

-- | Convert 'GraphModel' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe GraphModel) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_graph_view_model_get_type
    gvalueSet_ :: Ptr GValue -> Maybe GraphModel -> IO ()
gvalueSet_ Ptr GValue
gv Maybe GraphModel
P.Nothing = Ptr GValue -> Ptr GraphModel -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr GraphModel
forall a. Ptr a
FP.nullPtr :: FP.Ptr GraphModel)
    gvalueSet_ Ptr GValue
gv (P.Just GraphModel
obj) = GraphModel -> (Ptr GraphModel -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GraphModel
obj (Ptr GValue -> Ptr GraphModel -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe GraphModel)
gvalueGet_ Ptr GValue
gv = do
        Ptr GraphModel
ptr <- Ptr GValue -> IO (Ptr GraphModel)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr GraphModel)
        if Ptr GraphModel
ptr Ptr GraphModel -> Ptr GraphModel -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr GraphModel
forall a. Ptr a
FP.nullPtr
        then GraphModel -> Maybe GraphModel
forall a. a -> Maybe a
P.Just (GraphModel -> Maybe GraphModel)
-> IO GraphModel -> IO (Maybe GraphModel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr GraphModel -> GraphModel)
-> Ptr GraphModel -> IO GraphModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr GraphModel -> GraphModel
GraphModel Ptr GraphModel
ptr
        else Maybe GraphModel -> IO (Maybe GraphModel)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GraphModel
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveGraphModelMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveGraphModelMethod "addColumn" o = GraphModelAddColumnMethodInfo
    ResolveGraphModelMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGraphModelMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGraphModelMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGraphModelMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGraphModelMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGraphModelMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGraphModelMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGraphModelMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGraphModelMethod "push" o = GraphModelPushMethodInfo
    ResolveGraphModelMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGraphModelMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGraphModelMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGraphModelMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGraphModelMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGraphModelMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGraphModelMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGraphModelMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGraphModelMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGraphModelMethod "getEndTime" o = GraphModelGetEndTimeMethodInfo
    ResolveGraphModelMethod "getIterFirst" o = GraphModelGetIterFirstMethodInfo
    ResolveGraphModelMethod "getIterLast" o = GraphModelGetIterLastMethodInfo
    ResolveGraphModelMethod "getMaxSamples" o = GraphModelGetMaxSamplesMethodInfo
    ResolveGraphModelMethod "getNColumns" o = GraphModelGetNColumnsMethodInfo
    ResolveGraphModelMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGraphModelMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGraphModelMethod "getTimespan" o = GraphModelGetTimespanMethodInfo
    ResolveGraphModelMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGraphModelMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGraphModelMethod "setMaxSamples" o = GraphModelSetMaxSamplesMethodInfo
    ResolveGraphModelMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGraphModelMethod "setTimespan" o = GraphModelSetTimespanMethodInfo
    ResolveGraphModelMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveGraphModelMethod t GraphModel, O.OverloadedMethod info GraphModel p, R.HasField t GraphModel p) => R.HasField t GraphModel p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- signal GraphModel::changed
-- | /No description available in the introspection data./
type GraphModelChangedCallback =
    IO ()

type C_GraphModelChangedCallback =
    Ptr GraphModel ->                       -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_GraphModelChangedCallback`.
foreign import ccall "wrapper"
    mk_GraphModelChangedCallback :: C_GraphModelChangedCallback -> IO (FunPtr C_GraphModelChangedCallback)

wrap_GraphModelChangedCallback :: 
    GObject a => (a -> GraphModelChangedCallback) ->
    C_GraphModelChangedCallback
wrap_GraphModelChangedCallback :: forall a. GObject a => (a -> IO ()) -> C_GraphModelChangedCallback
wrap_GraphModelChangedCallback a -> IO ()
gi'cb Ptr GraphModel
gi'selfPtr Ptr ()
_ = do
    Ptr GraphModel -> (GraphModel -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr GraphModel
gi'selfPtr ((GraphModel -> IO ()) -> IO ()) -> (GraphModel -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \GraphModel
gi'self -> a -> IO ()
gi'cb (GraphModel -> a
forall a b. Coercible a b => a -> b
Coerce.coerce GraphModel
gi'self) 


-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' graphModel #changed callback
-- @
-- 
-- 
onGraphModelChanged :: (IsGraphModel a, MonadIO m) => a -> ((?self :: a) => GraphModelChangedCallback) -> m SignalHandlerId
onGraphModelChanged :: forall a (m :: * -> *).
(IsGraphModel a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onGraphModelChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_GraphModelChangedCallback
wrapped' = (a -> IO ()) -> C_GraphModelChangedCallback
forall a. GObject a => (a -> IO ()) -> C_GraphModelChangedCallback
wrap_GraphModelChangedCallback a -> IO ()
wrapped
    FunPtr C_GraphModelChangedCallback
wrapped'' <- C_GraphModelChangedCallback
-> IO (FunPtr C_GraphModelChangedCallback)
mk_GraphModelChangedCallback C_GraphModelChangedCallback
wrapped'
    a
-> Text
-> FunPtr C_GraphModelChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_GraphModelChangedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' graphModel #changed callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterGraphModelChanged :: (IsGraphModel a, MonadIO m) => a -> ((?self :: a) => GraphModelChangedCallback) -> m SignalHandlerId
afterGraphModelChanged :: forall a (m :: * -> *).
(IsGraphModel a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterGraphModelChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_GraphModelChangedCallback
wrapped' = (a -> IO ()) -> C_GraphModelChangedCallback
forall a. GObject a => (a -> IO ()) -> C_GraphModelChangedCallback
wrap_GraphModelChangedCallback a -> IO ()
wrapped
    FunPtr C_GraphModelChangedCallback
wrapped'' <- C_GraphModelChangedCallback
-> IO (FunPtr C_GraphModelChangedCallback)
mk_GraphModelChangedCallback C_GraphModelChangedCallback
wrapped'
    a
-> Text
-> FunPtr C_GraphModelChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"changed" FunPtr C_GraphModelChangedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data GraphModelChangedSignalInfo
instance SignalInfo GraphModelChangedSignalInfo where
    type HaskellCallbackType GraphModelChangedSignalInfo = GraphModelChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_GraphModelChangedCallback cb
        cb'' <- mk_GraphModelChangedCallback cb'
        connectSignalFunPtr obj "changed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.GraphModel::changed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-GraphModel.html#g:signal:changed"})

#endif

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

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

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

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

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

-- VVV Prop "timespan"
   -- Type: TBasicType TInt64
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just False)

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

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

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

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

-- VVV Prop "value-max"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

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

#if defined(ENABLE_OVERLOADING)
data GraphModelValueMaxPropertyInfo
instance AttrInfo GraphModelValueMaxPropertyInfo where
    type AttrAllowedOps GraphModelValueMaxPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GraphModelValueMaxPropertyInfo = IsGraphModel
    type AttrSetTypeConstraint GraphModelValueMaxPropertyInfo = (~) Double
    type AttrTransferTypeConstraint GraphModelValueMaxPropertyInfo = (~) Double
    type AttrTransferType GraphModelValueMaxPropertyInfo = Double
    type AttrGetType GraphModelValueMaxPropertyInfo = Double
    type AttrLabel GraphModelValueMaxPropertyInfo = "value-max"
    type AttrOrigin GraphModelValueMaxPropertyInfo = GraphModel
    attrGet = getGraphModelValueMax
    attrSet = setGraphModelValueMax
    attrTransfer _ v = do
        return v
    attrConstruct = constructGraphModelValueMax
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.GraphModel.valueMax"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-GraphModel.html#g:attr:valueMax"
        })
#endif

-- VVV Prop "value-min"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

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

#if defined(ENABLE_OVERLOADING)
data GraphModelValueMinPropertyInfo
instance AttrInfo GraphModelValueMinPropertyInfo where
    type AttrAllowedOps GraphModelValueMinPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GraphModelValueMinPropertyInfo = IsGraphModel
    type AttrSetTypeConstraint GraphModelValueMinPropertyInfo = (~) Double
    type AttrTransferTypeConstraint GraphModelValueMinPropertyInfo = (~) Double
    type AttrTransferType GraphModelValueMinPropertyInfo = Double
    type AttrGetType GraphModelValueMinPropertyInfo = Double
    type AttrLabel GraphModelValueMinPropertyInfo = "value-min"
    type AttrOrigin GraphModelValueMinPropertyInfo = GraphModel
    attrGet = getGraphModelValueMin
    attrSet = setGraphModelValueMin
    attrTransfer _ v = do
        return v
    attrConstruct = constructGraphModelValueMin
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Dazzle.Objects.GraphModel.valueMin"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-GraphModel.html#g:attr:valueMin"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GraphModel
type instance O.AttributeList GraphModel = GraphModelAttributeList
type GraphModelAttributeList = ('[ '("maxSamples", GraphModelMaxSamplesPropertyInfo), '("timespan", GraphModelTimespanPropertyInfo), '("valueMax", GraphModelValueMaxPropertyInfo), '("valueMin", GraphModelValueMinPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
graphModelMaxSamples :: AttrLabelProxy "maxSamples"
graphModelMaxSamples = AttrLabelProxy

graphModelTimespan :: AttrLabelProxy "timespan"
graphModelTimespan = AttrLabelProxy

graphModelValueMax :: AttrLabelProxy "valueMax"
graphModelValueMax = AttrLabelProxy

graphModelValueMin :: AttrLabelProxy "valueMin"
graphModelValueMin = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "dzl_graph_view_model_new" dzl_graph_view_model_new :: 
    IO (Ptr GraphModel)

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

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "dzl_graph_view_model_add_column" dzl_graph_view_model_add_column :: 
    Ptr GraphModel ->                       -- self : TInterface (Name {namespace = "Dazzle", name = "GraphModel"})
    Ptr Dazzle.GraphColumn.GraphColumn ->   -- column : TInterface (Name {namespace = "Dazzle", name = "GraphColumn"})
    IO Word32

-- | /No description available in the introspection data./
graphModelAddColumn ::
    (B.CallStack.HasCallStack, MonadIO m, IsGraphModel a, Dazzle.GraphColumn.IsGraphColumn b) =>
    a
    -> b
    -> m Word32
graphModelAddColumn :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsGraphModel a, IsGraphColumn b) =>
a -> b -> m Word32
graphModelAddColumn a
self b
column = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModel
self' <- a -> IO (Ptr GraphModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GraphColumn
column' <- b -> IO (Ptr GraphColumn)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
column
    Word32
result <- Ptr GraphModel -> Ptr GraphColumn -> IO Word32
dzl_graph_view_model_add_column Ptr GraphModel
self' Ptr GraphColumn
column'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
column
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data GraphModelAddColumnMethodInfo
instance (signature ~ (b -> m Word32), MonadIO m, IsGraphModel a, Dazzle.GraphColumn.IsGraphColumn b) => O.OverloadedMethod GraphModelAddColumnMethodInfo a signature where
    overloadedMethod = graphModelAddColumn

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data GraphModelGetEndTimeMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelGetEndTimeMethodInfo a signature where
    overloadedMethod = graphModelGetEndTime

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


#endif

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

foreign import ccall "dzl_graph_view_model_get_iter_first" dzl_graph_view_model_get_iter_first :: 
    Ptr GraphModel ->                       -- self : TInterface (Name {namespace = "Dazzle", name = "GraphModel"})
    Ptr Dazzle.GraphModelIter.GraphModelIter -> -- iter : TInterface (Name {namespace = "Dazzle", name = "GraphModelIter"})
    IO CInt

-- | /No description available in the introspection data./
graphModelGetIterFirst ::
    (B.CallStack.HasCallStack, MonadIO m, IsGraphModel a) =>
    a
    -> Dazzle.GraphModelIter.GraphModelIter
    -> m Bool
graphModelGetIterFirst :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGraphModel a) =>
a -> GraphModelIter -> m Bool
graphModelGetIterFirst a
self GraphModelIter
iter = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModel
self' <- a -> IO (Ptr GraphModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GraphModelIter
iter' <- GraphModelIter -> IO (Ptr GraphModelIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GraphModelIter
iter
    CInt
result <- Ptr GraphModel -> Ptr GraphModelIter -> IO CInt
dzl_graph_view_model_get_iter_first Ptr GraphModel
self' Ptr GraphModelIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    GraphModelIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GraphModelIter
iter
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GraphModelGetIterFirstMethodInfo
instance (signature ~ (Dazzle.GraphModelIter.GraphModelIter -> m Bool), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelGetIterFirstMethodInfo a signature where
    overloadedMethod = graphModelGetIterFirst

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


#endif

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

foreign import ccall "dzl_graph_view_model_get_iter_last" dzl_graph_view_model_get_iter_last :: 
    Ptr GraphModel ->                       -- self : TInterface (Name {namespace = "Dazzle", name = "GraphModel"})
    Ptr Dazzle.GraphModelIter.GraphModelIter -> -- iter : TInterface (Name {namespace = "Dazzle", name = "GraphModelIter"})
    IO CInt

-- | /No description available in the introspection data./
graphModelGetIterLast ::
    (B.CallStack.HasCallStack, MonadIO m, IsGraphModel a) =>
    a
    -> Dazzle.GraphModelIter.GraphModelIter
    -> m Bool
graphModelGetIterLast :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGraphModel a) =>
a -> GraphModelIter -> m Bool
graphModelGetIterLast a
self GraphModelIter
iter = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModel
self' <- a -> IO (Ptr GraphModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GraphModelIter
iter' <- GraphModelIter -> IO (Ptr GraphModelIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GraphModelIter
iter
    CInt
result <- Ptr GraphModel -> Ptr GraphModelIter -> IO CInt
dzl_graph_view_model_get_iter_last Ptr GraphModel
self' Ptr GraphModelIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    GraphModelIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GraphModelIter
iter
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GraphModelGetIterLastMethodInfo
instance (signature ~ (Dazzle.GraphModelIter.GraphModelIter -> m Bool), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelGetIterLastMethodInfo a signature where
    overloadedMethod = graphModelGetIterLast

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data GraphModelGetMaxSamplesMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelGetMaxSamplesMethodInfo a signature where
    overloadedMethod = graphModelGetMaxSamples

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data GraphModelGetNColumnsMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelGetNColumnsMethodInfo a signature where
    overloadedMethod = graphModelGetNColumns

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data GraphModelGetTimespanMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelGetTimespanMethodInfo a signature where
    overloadedMethod = graphModelGetTimespan

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


#endif

-- method GraphModel::push
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Dazzle" , name = "GraphModel" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Table to push to" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Dazzle" , name = "GraphModelIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Newly created #DzlGraphModelIter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timestamp"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Time of new event" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_graph_view_model_push" dzl_graph_view_model_push :: 
    Ptr GraphModel ->                       -- self : TInterface (Name {namespace = "Dazzle", name = "GraphModel"})
    Ptr Dazzle.GraphModelIter.GraphModelIter -> -- iter : TInterface (Name {namespace = "Dazzle", name = "GraphModelIter"})
    Int64 ->                                -- timestamp : TBasicType TInt64
    IO ()

-- | /No description available in the introspection data./
graphModelPush ::
    (B.CallStack.HasCallStack, MonadIO m, IsGraphModel a) =>
    a
    -- ^ /@self@/: Table to push to
    -> Int64
    -- ^ /@timestamp@/: Time of new event
    -> m (Dazzle.GraphModelIter.GraphModelIter)
graphModelPush :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGraphModel a) =>
a -> Int64 -> m GraphModelIter
graphModelPush a
self Int64
timestamp = IO GraphModelIter -> m GraphModelIter
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GraphModelIter -> m GraphModelIter)
-> IO GraphModelIter -> m GraphModelIter
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModel
self' <- a -> IO (Ptr GraphModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GraphModelIter
iter <- Int -> IO (Ptr GraphModelIter)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
64 :: IO (Ptr Dazzle.GraphModelIter.GraphModelIter)
    Ptr GraphModel -> Ptr GraphModelIter -> Int64 -> IO ()
dzl_graph_view_model_push Ptr GraphModel
self' Ptr GraphModelIter
iter Int64
timestamp
    GraphModelIter
iter' <- ((ManagedPtr GraphModelIter -> GraphModelIter)
-> Ptr GraphModelIter -> IO GraphModelIter
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr GraphModelIter -> GraphModelIter
Dazzle.GraphModelIter.GraphModelIter) Ptr GraphModelIter
iter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    GraphModelIter -> IO GraphModelIter
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GraphModelIter
iter'

#if defined(ENABLE_OVERLOADING)
data GraphModelPushMethodInfo
instance (signature ~ (Int64 -> m (Dazzle.GraphModelIter.GraphModelIter)), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelPushMethodInfo a signature where
    overloadedMethod = graphModelPush

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data GraphModelSetMaxSamplesMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelSetMaxSamplesMethodInfo a signature where
    overloadedMethod = graphModelSetMaxSamples

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


#endif

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

foreign import ccall "dzl_graph_view_model_set_timespan" dzl_graph_view_model_set_timespan :: 
    Ptr GraphModel ->                       -- self : TInterface (Name {namespace = "Dazzle", name = "GraphModel"})
    Int64 ->                                -- timespan : TBasicType TInt64
    IO ()

-- | /No description available in the introspection data./
graphModelSetTimespan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGraphModel a) =>
    a
    -> Int64
    -> m ()
graphModelSetTimespan :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGraphModel a) =>
a -> Int64 -> m ()
graphModelSetTimespan a
self Int64
timespan = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModel
self' <- a -> IO (Ptr GraphModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GraphModel -> Int64 -> IO ()
dzl_graph_view_model_set_timespan Ptr GraphModel
self' Int64
timespan
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GraphModelSetTimespanMethodInfo
instance (signature ~ (Int64 -> m ()), MonadIO m, IsGraphModel a) => O.OverloadedMethod GraphModelSetTimespanMethodInfo a signature where
    overloadedMethod = graphModelSetTimespan

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


#endif

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

foreign import ccall "dzl_graph_view_model_iter_get_timestamp" dzl_graph_view_model_iter_get_timestamp :: 
    Ptr Dazzle.GraphModelIter.GraphModelIter -> -- iter : TInterface (Name {namespace = "Dazzle", name = "GraphModelIter"})
    IO Int64

-- | /No description available in the introspection data./
graphModelIterGetTimestamp ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Dazzle.GraphModelIter.GraphModelIter
    -> m Int64
graphModelIterGetTimestamp :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GraphModelIter -> m Int64
graphModelIterGetTimestamp GraphModelIter
iter = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModelIter
iter' <- GraphModelIter -> IO (Ptr GraphModelIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GraphModelIter
iter
    Int64
result <- Ptr GraphModelIter -> IO Int64
dzl_graph_view_model_iter_get_timestamp Ptr GraphModelIter
iter'
    GraphModelIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GraphModelIter
iter
    Int64 -> IO Int64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result

#if defined(ENABLE_OVERLOADING)
#endif

-- method GraphModel::iter_get_value
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Dazzle" , name = "GraphModelIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "column"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_graph_view_model_iter_get_value" dzl_graph_view_model_iter_get_value :: 
    Ptr Dazzle.GraphModelIter.GraphModelIter -> -- iter : TInterface (Name {namespace = "Dazzle", name = "GraphModelIter"})
    Word32 ->                               -- column : TBasicType TUInt
    Ptr GValue ->                           -- value : TGValue
    IO ()

-- | /No description available in the introspection data./
graphModelIterGetValue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Dazzle.GraphModelIter.GraphModelIter
    -> Word32
    -> GValue
    -> m ()
graphModelIterGetValue :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GraphModelIter -> Word32 -> GValue -> m ()
graphModelIterGetValue GraphModelIter
iter Word32
column GValue
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModelIter
iter' <- GraphModelIter -> IO (Ptr GraphModelIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GraphModelIter
iter
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    Ptr GraphModelIter -> Word32 -> Ptr GValue -> IO ()
dzl_graph_view_model_iter_get_value Ptr GraphModelIter
iter' Word32
column Ptr GValue
value'
    GraphModelIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GraphModelIter
iter
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "dzl_graph_view_model_iter_next" dzl_graph_view_model_iter_next :: 
    Ptr Dazzle.GraphModelIter.GraphModelIter -> -- iter : TInterface (Name {namespace = "Dazzle", name = "GraphModelIter"})
    IO CInt

-- | /No description available in the introspection data./
graphModelIterNext ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Dazzle.GraphModelIter.GraphModelIter
    -> m Bool
graphModelIterNext :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GraphModelIter -> m Bool
graphModelIterNext GraphModelIter
iter = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModelIter
iter' <- GraphModelIter -> IO (Ptr GraphModelIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GraphModelIter
iter
    CInt
result <- Ptr GraphModelIter -> IO CInt
dzl_graph_view_model_iter_next Ptr GraphModelIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    GraphModelIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GraphModelIter
iter
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method GraphModel::iter_set
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Dazzle" , name = "GraphModelIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the iter to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "column"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the column to set" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value for the column"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dzl_graph_view_model_iter_set_value" dzl_graph_view_model_iter_set_value :: 
    Ptr Dazzle.GraphModelIter.GraphModelIter -> -- iter : TInterface (Name {namespace = "Dazzle", name = "GraphModelIter"})
    Word32 ->                               -- column : TBasicType TUInt
    Ptr GValue ->                           -- value : TGValue
    IO ()

-- | Sets an individual value within a specific column.
-- 
-- /Since: 3.30/
graphModelIterSet ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Dazzle.GraphModelIter.GraphModelIter
    -- ^ /@iter@/: the iter to set
    -> Word32
    -- ^ /@column@/: the column to set
    -> GValue
    -- ^ /@value@/: the new value for the column
    -> m ()
graphModelIterSet :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GraphModelIter -> Word32 -> GValue -> m ()
graphModelIterSet GraphModelIter
iter Word32
column GValue
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphModelIter
iter' <- GraphModelIter -> IO (Ptr GraphModelIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GraphModelIter
iter
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    Ptr GraphModelIter -> Word32 -> Ptr GValue -> IO ()
dzl_graph_view_model_iter_set_value Ptr GraphModelIter
iter' Word32
column Ptr GValue
value'
    GraphModelIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GraphModelIter
iter
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif