{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkLayoutChild@ subclass for children in a @GtkGridLayout@.

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

module GI.Gtk.Objects.GridLayoutChild
    ( 

-- * Exported types
    GridLayoutChild(..)                     ,
    IsGridLayoutChild                       ,
    toGridLayoutChild                       ,


 -- * 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
-- [getChildWidget]("GI.Gtk.Objects.LayoutChild#g:method:getChildWidget"), [getColumn]("GI.Gtk.Objects.GridLayoutChild#g:method:getColumn"), [getColumnSpan]("GI.Gtk.Objects.GridLayoutChild#g:method:getColumnSpan"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getLayoutManager]("GI.Gtk.Objects.LayoutChild#g:method:getLayoutManager"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRow]("GI.Gtk.Objects.GridLayoutChild#g:method:getRow"), [getRowSpan]("GI.Gtk.Objects.GridLayoutChild#g:method:getRowSpan").
-- 
-- ==== Setters
-- [setColumn]("GI.Gtk.Objects.GridLayoutChild#g:method:setColumn"), [setColumnSpan]("GI.Gtk.Objects.GridLayoutChild#g:method:setColumnSpan"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRow]("GI.Gtk.Objects.GridLayoutChild#g:method:setRow"), [setRowSpan]("GI.Gtk.Objects.GridLayoutChild#g:method:setRowSpan").

#if defined(ENABLE_OVERLOADING)
    ResolveGridLayoutChildMethod            ,
#endif

-- ** getColumn #method:getColumn#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildGetColumnMethodInfo      ,
#endif
    gridLayoutChildGetColumn                ,


-- ** getColumnSpan #method:getColumnSpan#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildGetColumnSpanMethodInfo  ,
#endif
    gridLayoutChildGetColumnSpan            ,


-- ** getRow #method:getRow#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildGetRowMethodInfo         ,
#endif
    gridLayoutChildGetRow                   ,


-- ** getRowSpan #method:getRowSpan#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildGetRowSpanMethodInfo     ,
#endif
    gridLayoutChildGetRowSpan               ,


-- ** setColumn #method:setColumn#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildSetColumnMethodInfo      ,
#endif
    gridLayoutChildSetColumn                ,


-- ** setColumnSpan #method:setColumnSpan#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildSetColumnSpanMethodInfo  ,
#endif
    gridLayoutChildSetColumnSpan            ,


-- ** setRow #method:setRow#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildSetRowMethodInfo         ,
#endif
    gridLayoutChildSetRow                   ,


-- ** setRowSpan #method:setRowSpan#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildSetRowSpanMethodInfo     ,
#endif
    gridLayoutChildSetRowSpan               ,




 -- * Properties


-- ** column #attr:column#
-- | The column to place the child in.

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildColumnPropertyInfo       ,
#endif
    constructGridLayoutChildColumn          ,
    getGridLayoutChildColumn                ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutChildColumn                   ,
#endif
    setGridLayoutChildColumn                ,


-- ** columnSpan #attr:columnSpan#
-- | The number of columns the child spans to.

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildColumnSpanPropertyInfo   ,
#endif
    constructGridLayoutChildColumnSpan      ,
    getGridLayoutChildColumnSpan            ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutChildColumnSpan               ,
#endif
    setGridLayoutChildColumnSpan            ,


-- ** row #attr:row#
-- | The row to place the child in.

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildRowPropertyInfo          ,
#endif
    constructGridLayoutChildRow             ,
    getGridLayoutChildRow                   ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutChildRow                      ,
#endif
    setGridLayoutChildRow                   ,


-- ** rowSpan #attr:rowSpan#
-- | The number of rows the child spans to.

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildRowSpanPropertyInfo      ,
#endif
    constructGridLayoutChildRowSpan         ,
    getGridLayoutChildRowSpan               ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutChildRowSpan                  ,
#endif
    setGridLayoutChildRowSpan               ,




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

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

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

foreign import ccall "gtk_grid_layout_child_get_type"
    c_gtk_grid_layout_child_get_type :: IO B.Types.GType

instance B.Types.TypedObject GridLayoutChild where
    glibType :: IO GType
glibType = IO GType
c_gtk_grid_layout_child_get_type

instance B.Types.GObject GridLayoutChild

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

instance O.HasParentTypes GridLayoutChild
type instance O.ParentTypes GridLayoutChild = '[Gtk.LayoutChild.LayoutChild, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveGridLayoutChildMethod (t :: Symbol) (o :: *) :: * where
    ResolveGridLayoutChildMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGridLayoutChildMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGridLayoutChildMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGridLayoutChildMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGridLayoutChildMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGridLayoutChildMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGridLayoutChildMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGridLayoutChildMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGridLayoutChildMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGridLayoutChildMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGridLayoutChildMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGridLayoutChildMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGridLayoutChildMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGridLayoutChildMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGridLayoutChildMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGridLayoutChildMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGridLayoutChildMethod "getChildWidget" o = Gtk.LayoutChild.LayoutChildGetChildWidgetMethodInfo
    ResolveGridLayoutChildMethod "getColumn" o = GridLayoutChildGetColumnMethodInfo
    ResolveGridLayoutChildMethod "getColumnSpan" o = GridLayoutChildGetColumnSpanMethodInfo
    ResolveGridLayoutChildMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGridLayoutChildMethod "getLayoutManager" o = Gtk.LayoutChild.LayoutChildGetLayoutManagerMethodInfo
    ResolveGridLayoutChildMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGridLayoutChildMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGridLayoutChildMethod "getRow" o = GridLayoutChildGetRowMethodInfo
    ResolveGridLayoutChildMethod "getRowSpan" o = GridLayoutChildGetRowSpanMethodInfo
    ResolveGridLayoutChildMethod "setColumn" o = GridLayoutChildSetColumnMethodInfo
    ResolveGridLayoutChildMethod "setColumnSpan" o = GridLayoutChildSetColumnSpanMethodInfo
    ResolveGridLayoutChildMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGridLayoutChildMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGridLayoutChildMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGridLayoutChildMethod "setRow" o = GridLayoutChildSetRowMethodInfo
    ResolveGridLayoutChildMethod "setRowSpan" o = GridLayoutChildSetRowSpanMethodInfo
    ResolveGridLayoutChildMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@column@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutChildColumn :: (IsGridLayoutChild o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridLayoutChildColumn :: forall o (m :: * -> *).
(IsGridLayoutChild o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructGridLayoutChildColumn Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"column" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildColumnPropertyInfo
instance AttrInfo GridLayoutChildColumnPropertyInfo where
    type AttrAllowedOps GridLayoutChildColumnPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutChildColumnPropertyInfo = IsGridLayoutChild
    type AttrSetTypeConstraint GridLayoutChildColumnPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutChildColumnPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutChildColumnPropertyInfo = Int32
    type AttrGetType GridLayoutChildColumnPropertyInfo = Int32
    type AttrLabel GridLayoutChildColumnPropertyInfo = "column"
    type AttrOrigin GridLayoutChildColumnPropertyInfo = GridLayoutChild
    attrGet = getGridLayoutChildColumn
    attrSet = setGridLayoutChildColumn
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutChildColumn
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.column"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#g:attr:column"
        })
#endif

-- VVV Prop "column-span"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@column-span@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayoutChild [ #columnSpan 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutChildColumnSpan :: (MonadIO m, IsGridLayoutChild o) => o -> Int32 -> m ()
setGridLayoutChildColumnSpan :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayoutChild o) =>
o -> Int32 -> m ()
setGridLayoutChildColumnSpan o
obj Int32
val = IO () -> m ()
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"column-span" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@column-span@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutChildColumnSpan :: (IsGridLayoutChild o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridLayoutChildColumnSpan :: forall o (m :: * -> *).
(IsGridLayoutChild o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructGridLayoutChildColumnSpan Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"column-span" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildColumnSpanPropertyInfo
instance AttrInfo GridLayoutChildColumnSpanPropertyInfo where
    type AttrAllowedOps GridLayoutChildColumnSpanPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutChildColumnSpanPropertyInfo = IsGridLayoutChild
    type AttrSetTypeConstraint GridLayoutChildColumnSpanPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutChildColumnSpanPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutChildColumnSpanPropertyInfo = Int32
    type AttrGetType GridLayoutChildColumnSpanPropertyInfo = Int32
    type AttrLabel GridLayoutChildColumnSpanPropertyInfo = "column-span"
    type AttrOrigin GridLayoutChildColumnSpanPropertyInfo = GridLayoutChild
    attrGet = getGridLayoutChildColumnSpan
    attrSet = setGridLayoutChildColumnSpan
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutChildColumnSpan
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.columnSpan"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#g:attr:columnSpan"
        })
#endif

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@row@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutChildRow :: (IsGridLayoutChild o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridLayoutChildRow :: forall o (m :: * -> *).
(IsGridLayoutChild o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructGridLayoutChildRow Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"row" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildRowPropertyInfo
instance AttrInfo GridLayoutChildRowPropertyInfo where
    type AttrAllowedOps GridLayoutChildRowPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutChildRowPropertyInfo = IsGridLayoutChild
    type AttrSetTypeConstraint GridLayoutChildRowPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutChildRowPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutChildRowPropertyInfo = Int32
    type AttrGetType GridLayoutChildRowPropertyInfo = Int32
    type AttrLabel GridLayoutChildRowPropertyInfo = "row"
    type AttrOrigin GridLayoutChildRowPropertyInfo = GridLayoutChild
    attrGet = getGridLayoutChildRow
    attrSet = setGridLayoutChildRow
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutChildRow
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.row"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#g:attr:row"
        })
#endif

-- VVV Prop "row-span"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@row-span@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayoutChild [ #rowSpan 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutChildRowSpan :: (MonadIO m, IsGridLayoutChild o) => o -> Int32 -> m ()
setGridLayoutChildRowSpan :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayoutChild o) =>
o -> Int32 -> m ()
setGridLayoutChildRowSpan o
obj Int32
val = IO () -> m ()
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"row-span" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@row-span@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutChildRowSpan :: (IsGridLayoutChild o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridLayoutChildRowSpan :: forall o (m :: * -> *).
(IsGridLayoutChild o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructGridLayoutChildRowSpan Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"row-span" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildRowSpanPropertyInfo
instance AttrInfo GridLayoutChildRowSpanPropertyInfo where
    type AttrAllowedOps GridLayoutChildRowSpanPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutChildRowSpanPropertyInfo = IsGridLayoutChild
    type AttrSetTypeConstraint GridLayoutChildRowSpanPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutChildRowSpanPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutChildRowSpanPropertyInfo = Int32
    type AttrGetType GridLayoutChildRowSpanPropertyInfo = Int32
    type AttrLabel GridLayoutChildRowSpanPropertyInfo = "row-span"
    type AttrOrigin GridLayoutChildRowSpanPropertyInfo = GridLayoutChild
    attrGet = getGridLayoutChildRowSpan
    attrSet = setGridLayoutChildRowSpan
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutChildRowSpan
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.rowSpan"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#g:attr:rowSpan"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GridLayoutChild
type instance O.AttributeList GridLayoutChild = GridLayoutChildAttributeList
type GridLayoutChildAttributeList = ('[ '("childWidget", Gtk.LayoutChild.LayoutChildChildWidgetPropertyInfo), '("column", GridLayoutChildColumnPropertyInfo), '("columnSpan", GridLayoutChildColumnSpanPropertyInfo), '("layoutManager", Gtk.LayoutChild.LayoutChildLayoutManagerPropertyInfo), '("row", GridLayoutChildRowPropertyInfo), '("rowSpan", GridLayoutChildRowSpanPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
gridLayoutChildColumn :: AttrLabelProxy "column"
gridLayoutChildColumn = AttrLabelProxy

gridLayoutChildColumnSpan :: AttrLabelProxy "columnSpan"
gridLayoutChildColumnSpan = AttrLabelProxy

gridLayoutChildRow :: AttrLabelProxy "row"
gridLayoutChildRow = AttrLabelProxy

gridLayoutChildRowSpan :: AttrLabelProxy "rowSpan"
gridLayoutChildRowSpan = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GridLayoutChild = GridLayoutChildSignalList
type GridLayoutChildSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_grid_layout_child_get_column" gtk_grid_layout_child_get_column :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    IO Int32

-- | Retrieves the column number to which /@child@/ attaches its left side.
gridLayoutChildGetColumn ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a @GtkGridLayoutChild@
    -> m Int32
    -- ^ __Returns:__ the column number
gridLayoutChildGetColumn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayoutChild a) =>
a -> m Int32
gridLayoutChildGetColumn a
child = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Int32
result <- Ptr GridLayoutChild -> IO Int32
gtk_grid_layout_child_get_column Ptr GridLayoutChild
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildGetColumnMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayoutChild a) => O.OverloadedMethod GridLayoutChildGetColumnMethodInfo a signature where
    overloadedMethod = gridLayoutChildGetColumn

instance O.OverloadedMethodInfo GridLayoutChildGetColumnMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.gridLayoutChildGetColumn",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#v:gridLayoutChildGetColumn"
        })


#endif

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

foreign import ccall "gtk_grid_layout_child_get_column_span" gtk_grid_layout_child_get_column_span :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    IO Int32

-- | Retrieves the number of columns that /@child@/ spans to.
gridLayoutChildGetColumnSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a @GtkGridLayoutChild@
    -> m Int32
    -- ^ __Returns:__ the number of columns
gridLayoutChildGetColumnSpan :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayoutChild a) =>
a -> m Int32
gridLayoutChildGetColumnSpan a
child = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Int32
result <- Ptr GridLayoutChild -> IO Int32
gtk_grid_layout_child_get_column_span Ptr GridLayoutChild
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildGetColumnSpanMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayoutChild a) => O.OverloadedMethod GridLayoutChildGetColumnSpanMethodInfo a signature where
    overloadedMethod = gridLayoutChildGetColumnSpan

instance O.OverloadedMethodInfo GridLayoutChildGetColumnSpanMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.gridLayoutChildGetColumnSpan",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#v:gridLayoutChildGetColumnSpan"
        })


#endif

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

foreign import ccall "gtk_grid_layout_child_get_row" gtk_grid_layout_child_get_row :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    IO Int32

-- | Retrieves the row number to which /@child@/ attaches its top side.
gridLayoutChildGetRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a @GtkGridLayoutChild@
    -> m Int32
    -- ^ __Returns:__ the row number
gridLayoutChildGetRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayoutChild a) =>
a -> m Int32
gridLayoutChildGetRow a
child = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Int32
result <- Ptr GridLayoutChild -> IO Int32
gtk_grid_layout_child_get_row Ptr GridLayoutChild
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildGetRowMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayoutChild a) => O.OverloadedMethod GridLayoutChildGetRowMethodInfo a signature where
    overloadedMethod = gridLayoutChildGetRow

instance O.OverloadedMethodInfo GridLayoutChildGetRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.gridLayoutChildGetRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#v:gridLayoutChildGetRow"
        })


#endif

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

foreign import ccall "gtk_grid_layout_child_get_row_span" gtk_grid_layout_child_get_row_span :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    IO Int32

-- | Retrieves the number of rows that /@child@/ spans to.
gridLayoutChildGetRowSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a @GtkGridLayoutChild@
    -> m Int32
    -- ^ __Returns:__ the number of row
gridLayoutChildGetRowSpan :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayoutChild a) =>
a -> m Int32
gridLayoutChildGetRowSpan a
child = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Int32
result <- Ptr GridLayoutChild -> IO Int32
gtk_grid_layout_child_get_row_span Ptr GridLayoutChild
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildGetRowSpanMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayoutChild a) => O.OverloadedMethod GridLayoutChildGetRowSpanMethodInfo a signature where
    overloadedMethod = gridLayoutChildGetRowSpan

instance O.OverloadedMethodInfo GridLayoutChildGetRowSpanMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.gridLayoutChildGetRowSpan",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#v:gridLayoutChildGetRowSpan"
        })


#endif

-- method GridLayoutChild::set_column
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayoutChild" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkGridLayoutChild`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "column"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attach point for @child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_child_set_column" gtk_grid_layout_child_set_column :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    Int32 ->                                -- column : TBasicType TInt
    IO ()

-- | Sets the column number to attach the left side of /@child@/.
gridLayoutChildSetColumn ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a @GtkGridLayoutChild@
    -> Int32
    -- ^ /@column@/: the attach point for /@child@/
    -> m ()
gridLayoutChildSetColumn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayoutChild a) =>
a -> Int32 -> m ()
gridLayoutChildSetColumn a
child Int32
column = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Ptr GridLayoutChild -> Int32 -> IO ()
gtk_grid_layout_child_set_column Ptr GridLayoutChild
child' Int32
column
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildSetColumnMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayoutChild a) => O.OverloadedMethod GridLayoutChildSetColumnMethodInfo a signature where
    overloadedMethod = gridLayoutChildSetColumn

instance O.OverloadedMethodInfo GridLayoutChildSetColumnMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.gridLayoutChildSetColumn",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#v:gridLayoutChildSetColumn"
        })


#endif

-- method GridLayoutChild::set_column_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayoutChild" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkGridLayoutChild`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "span"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the span of @child" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_child_set_column_span" gtk_grid_layout_child_set_column_span :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    Int32 ->                                -- span : TBasicType TInt
    IO ()

-- | Sets the number of columns /@child@/ spans to.
gridLayoutChildSetColumnSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a @GtkGridLayoutChild@
    -> Int32
    -- ^ /@span@/: the span of /@child@/
    -> m ()
gridLayoutChildSetColumnSpan :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayoutChild a) =>
a -> Int32 -> m ()
gridLayoutChildSetColumnSpan a
child Int32
span = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Ptr GridLayoutChild -> Int32 -> IO ()
gtk_grid_layout_child_set_column_span Ptr GridLayoutChild
child' Int32
span
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildSetColumnSpanMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayoutChild a) => O.OverloadedMethod GridLayoutChildSetColumnSpanMethodInfo a signature where
    overloadedMethod = gridLayoutChildSetColumnSpan

instance O.OverloadedMethodInfo GridLayoutChildSetColumnSpanMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.gridLayoutChildSetColumnSpan",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#v:gridLayoutChildSetColumnSpan"
        })


#endif

-- method GridLayoutChild::set_row
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayoutChild" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkGridLayoutChild`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "row"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the row for @child" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_child_set_row" gtk_grid_layout_child_set_row :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    Int32 ->                                -- row : TBasicType TInt
    IO ()

-- | Sets the row to place /@child@/ in.
gridLayoutChildSetRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a @GtkGridLayoutChild@
    -> Int32
    -- ^ /@row@/: the row for /@child@/
    -> m ()
gridLayoutChildSetRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayoutChild a) =>
a -> Int32 -> m ()
gridLayoutChildSetRow a
child Int32
row = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Ptr GridLayoutChild -> Int32 -> IO ()
gtk_grid_layout_child_set_row Ptr GridLayoutChild
child' Int32
row
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildSetRowMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayoutChild a) => O.OverloadedMethod GridLayoutChildSetRowMethodInfo a signature where
    overloadedMethod = gridLayoutChildSetRow

instance O.OverloadedMethodInfo GridLayoutChildSetRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.gridLayoutChildSetRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#v:gridLayoutChildSetRow"
        })


#endif

-- method GridLayoutChild::set_row_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayoutChild" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkGridLayoutChild`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "span"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the span of @child" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_child_set_row_span" gtk_grid_layout_child_set_row_span :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    Int32 ->                                -- span : TBasicType TInt
    IO ()

-- | Sets the number of rows /@child@/ spans to.
gridLayoutChildSetRowSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a @GtkGridLayoutChild@
    -> Int32
    -- ^ /@span@/: the span of /@child@/
    -> m ()
gridLayoutChildSetRowSpan :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayoutChild a) =>
a -> Int32 -> m ()
gridLayoutChildSetRowSpan a
child Int32
span = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Ptr GridLayoutChild -> Int32 -> IO ()
gtk_grid_layout_child_set_row_span Ptr GridLayoutChild
child' Int32
span
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildSetRowSpanMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayoutChild a) => O.OverloadedMethod GridLayoutChildSetRowSpanMethodInfo a signature where
    overloadedMethod = gridLayoutChildSetRowSpan

instance O.OverloadedMethodInfo GridLayoutChildSetRowSpanMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.GridLayoutChild.gridLayoutChildSetRowSpan",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-GridLayoutChild.html#v:gridLayoutChildSetRowSpan"
        })


#endif