{-# LANGUAGE TypeApplications #-}


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

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

module GI.Dazzle.Objects.GraphColumn
    ( 

-- * Exported types
    GraphColumn(..)                         ,
    IsGraphColumn                           ,
    toGraphColumn                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [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"), [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"), [getName]("GI.Dazzle.Objects.GraphColumn#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setName]("GI.Dazzle.Objects.GraphColumn#g:method:setName"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveGraphColumnMethod                ,
#endif

-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    GraphColumnGetNameMethodInfo            ,
#endif
    graphColumnGetName                      ,


-- ** new #method:new#

    graphColumnNew                          ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    GraphColumnSetNameMethodInfo            ,
#endif
    graphColumnSetName                      ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    GraphColumnNamePropertyInfo             ,
#endif
    constructGraphColumnName                ,
    getGraphColumnName                      ,
#if defined(ENABLE_OVERLOADING)
    graphColumnName                         ,
#endif
    setGraphColumnName                      ,


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

#if defined(ENABLE_OVERLOADING)
    GraphColumnValueTypePropertyInfo        ,
#endif
    constructGraphColumnValueType           ,
    getGraphColumnValueType                 ,
#if defined(ENABLE_OVERLOADING)
    graphColumnValueType                    ,
#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.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 qualified GI.GObject.Objects.Object as GObject.Object

#else
import qualified GI.GObject.Objects.Object as GObject.Object

#endif

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

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

foreign import ccall "dzl_graph_view_column_get_type"
    c_dzl_graph_view_column_get_type :: IO B.Types.GType

instance B.Types.TypedObject GraphColumn where
    glibType :: IO GType
glibType = IO GType
c_dzl_graph_view_column_get_type

instance B.Types.GObject GraphColumn

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveGraphColumnMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveGraphColumnMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGraphColumnMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGraphColumnMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGraphColumnMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGraphColumnMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGraphColumnMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGraphColumnMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGraphColumnMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGraphColumnMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGraphColumnMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGraphColumnMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGraphColumnMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGraphColumnMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGraphColumnMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGraphColumnMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGraphColumnMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGraphColumnMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGraphColumnMethod "getName" o = GraphColumnGetNameMethodInfo
    ResolveGraphColumnMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGraphColumnMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGraphColumnMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGraphColumnMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGraphColumnMethod "setName" o = GraphColumnSetNameMethodInfo
    ResolveGraphColumnMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGraphColumnMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' graphColumn #name
-- @
getGraphColumnName :: (MonadIO m, IsGraphColumn o) => o -> m T.Text
getGraphColumnName :: forall (m :: * -> *) o. (MonadIO m, IsGraphColumn o) => o -> m Text
getGraphColumnName o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getGraphColumnName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"

-- | Set the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' graphColumn [ #name 'Data.GI.Base.Attributes.:=' value ]
-- @
setGraphColumnName :: (MonadIO m, IsGraphColumn o) => o -> T.Text -> m ()
setGraphColumnName :: forall (m :: * -> *) o.
(MonadIO m, IsGraphColumn o) =>
o -> Text -> m ()
setGraphColumnName o
obj Text
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 -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGraphColumnName :: (IsGraphColumn o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructGraphColumnName :: forall o (m :: * -> *).
(IsGraphColumn o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructGraphColumnName Text
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 -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

-- VVV Prop "value-type"
   -- Type: TBasicType TGType
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@value-type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' graphColumn #valueType
-- @
getGraphColumnValueType :: (MonadIO m, IsGraphColumn o) => o -> m GType
getGraphColumnValueType :: forall (m :: * -> *) o.
(MonadIO m, IsGraphColumn o) =>
o -> m GType
getGraphColumnValueType o
obj = IO GType -> m GType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"value-type"

-- | Construct a `GValueConstruct` with valid value for the “@value-type@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGraphColumnValueType :: (IsGraphColumn o, MIO.MonadIO m) => GType -> m (GValueConstruct o)
constructGraphColumnValueType :: forall o (m :: * -> *).
(IsGraphColumn o, MonadIO m) =>
GType -> m (GValueConstruct o)
constructGraphColumnValueType GType
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 -> GType -> IO (GValueConstruct o)
forall o. String -> GType -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyGType String
"value-type" GType
val

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GraphColumn
type instance O.AttributeList GraphColumn = GraphColumnAttributeList
type GraphColumnAttributeList = ('[ '("name", GraphColumnNamePropertyInfo), '("valueType", GraphColumnValueTypePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
graphColumnName :: AttrLabelProxy "name"
graphColumnName = AttrLabelProxy

graphColumnValueType :: AttrLabelProxy "valueType"
graphColumnValueType = AttrLabelProxy

#endif

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

#endif

-- method GraphColumn::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , 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_type"
--           , argType = TBasicType TGType
--           , 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
--               (TInterface Name { namespace = "Dazzle" , name = "GraphColumn" })
-- throws : False
-- Skip return : False

foreign import ccall "dzl_graph_view_column_new" dzl_graph_view_column_new :: 
    CString ->                              -- name : TBasicType TUTF8
    CGType ->                               -- value_type : TBasicType TGType
    IO (Ptr GraphColumn)

-- | /No description available in the introspection data./
graphColumnNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -> GType
    -> m GraphColumn
graphColumnNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> GType -> m GraphColumn
graphColumnNew Text
name GType
valueType = IO GraphColumn -> m GraphColumn
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GraphColumn -> m GraphColumn)
-> IO GraphColumn -> m GraphColumn
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    let valueType' :: CGType
valueType' = GType -> CGType
gtypeToCGType GType
valueType
    Ptr GraphColumn
result <- CString -> CGType -> IO (Ptr GraphColumn)
dzl_graph_view_column_new CString
name' CGType
valueType'
    Text -> Ptr GraphColumn -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"graphColumnNew" Ptr GraphColumn
result
    GraphColumn
result' <- ((ManagedPtr GraphColumn -> GraphColumn)
-> Ptr GraphColumn -> IO GraphColumn
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr GraphColumn -> GraphColumn
GraphColumn) Ptr GraphColumn
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    GraphColumn -> IO GraphColumn
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GraphColumn
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method GraphColumn::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

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

-- | /No description available in the introspection data./
graphColumnGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsGraphColumn a) =>
    a
    -> m T.Text
graphColumnGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGraphColumn a) =>
a -> m Text
graphColumnGetName a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr GraphColumn
self' <- a -> IO (Ptr GraphColumn)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr GraphColumn -> IO CString
dzl_graph_view_column_get_name Ptr GraphColumn
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"graphColumnGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data GraphColumnGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsGraphColumn a) => O.OverloadedMethod GraphColumnGetNameMethodInfo a signature where
    overloadedMethod = graphColumnGetName

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


#endif

-- method GraphColumn::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , 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
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , 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_column_set_name" dzl_graph_view_column_set_name :: 
    Ptr GraphColumn ->                      -- self : TInterface (Name {namespace = "Dazzle", name = "GraphColumn"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | /No description available in the introspection data./
graphColumnSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsGraphColumn a) =>
    a
    -> T.Text
    -> m ()
graphColumnSetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGraphColumn a) =>
a -> Text -> m ()
graphColumnSetName a
self Text
name = 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 GraphColumn
self' <- a -> IO (Ptr GraphColumn)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr GraphColumn -> CString -> IO ()
dzl_graph_view_column_set_name Ptr GraphColumn
self' CString
name'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GraphColumnSetNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsGraphColumn a) => O.OverloadedMethod GraphColumnSetNameMethodInfo a signature where
    overloadedMethod = graphColumnSetName

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


#endif