{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GtkGridLayout is a layout manager which arranges child widgets in
-- rows and columns, with arbitrary positions and horizontal\/vertical
-- spans.
-- 
-- Children have an \"attach point\" defined by the horizontal and vertical
-- index of the cell they occupy; children can span multiple rows or columns.
-- The layout properties for setting the attach points and spans are set
-- using the t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild' associated to each child widget.
-- 
-- The behaviour of GtkGrid when several children occupy the same grid cell
-- is undefined.
-- 
-- GtkGridLayout can be used like a t'GI.Gtk.Objects.BoxLayout.BoxLayout' if all children are attached
-- to the same row or column; however, if you only ever need a single row or
-- column, you should consider using t'GI.Gtk.Objects.BoxLayout.BoxLayout'.

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

module GI.Gtk.Objects.GridLayout
    ( 

-- * Exported types
    GridLayout(..)                          ,
    IsGridLayout                            ,
    toGridLayout                            ,
    noGridLayout                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveGridLayoutMethod                 ,
#endif


-- ** getBaselineRow #method:getBaselineRow#

#if defined(ENABLE_OVERLOADING)
    GridLayoutGetBaselineRowMethodInfo      ,
#endif
    gridLayoutGetBaselineRow                ,


-- ** getColumnHomogeneous #method:getColumnHomogeneous#

#if defined(ENABLE_OVERLOADING)
    GridLayoutGetColumnHomogeneousMethodInfo,
#endif
    gridLayoutGetColumnHomogeneous          ,


-- ** getColumnSpacing #method:getColumnSpacing#

#if defined(ENABLE_OVERLOADING)
    GridLayoutGetColumnSpacingMethodInfo    ,
#endif
    gridLayoutGetColumnSpacing              ,


-- ** getRowBaselinePosition #method:getRowBaselinePosition#

#if defined(ENABLE_OVERLOADING)
    GridLayoutGetRowBaselinePositionMethodInfo,
#endif
    gridLayoutGetRowBaselinePosition        ,


-- ** getRowHomogeneous #method:getRowHomogeneous#

#if defined(ENABLE_OVERLOADING)
    GridLayoutGetRowHomogeneousMethodInfo   ,
#endif
    gridLayoutGetRowHomogeneous             ,


-- ** getRowSpacing #method:getRowSpacing#

#if defined(ENABLE_OVERLOADING)
    GridLayoutGetRowSpacingMethodInfo       ,
#endif
    gridLayoutGetRowSpacing                 ,


-- ** new #method:new#

    gridLayoutNew                           ,


-- ** setBaselineRow #method:setBaselineRow#

#if defined(ENABLE_OVERLOADING)
    GridLayoutSetBaselineRowMethodInfo      ,
#endif
    gridLayoutSetBaselineRow                ,


-- ** setColumnHomogeneous #method:setColumnHomogeneous#

#if defined(ENABLE_OVERLOADING)
    GridLayoutSetColumnHomogeneousMethodInfo,
#endif
    gridLayoutSetColumnHomogeneous          ,


-- ** setColumnSpacing #method:setColumnSpacing#

#if defined(ENABLE_OVERLOADING)
    GridLayoutSetColumnSpacingMethodInfo    ,
#endif
    gridLayoutSetColumnSpacing              ,


-- ** setRowBaselinePosition #method:setRowBaselinePosition#

#if defined(ENABLE_OVERLOADING)
    GridLayoutSetRowBaselinePositionMethodInfo,
#endif
    gridLayoutSetRowBaselinePosition        ,


-- ** setRowHomogeneous #method:setRowHomogeneous#

#if defined(ENABLE_OVERLOADING)
    GridLayoutSetRowHomogeneousMethodInfo   ,
#endif
    gridLayoutSetRowHomogeneous             ,


-- ** setRowSpacing #method:setRowSpacing#

#if defined(ENABLE_OVERLOADING)
    GridLayoutSetRowSpacingMethodInfo       ,
#endif
    gridLayoutSetRowSpacing                 ,




 -- * Properties
-- ** baselineRow #attr:baselineRow#
-- | The row to align to the baseline, when t'GI.Gtk.Objects.Widget.Widget':@/valign/@ is set
-- to 'GI.Gtk.Enums.AlignBaseline'.

#if defined(ENABLE_OVERLOADING)
    GridLayoutBaselineRowPropertyInfo       ,
#endif
    constructGridLayoutBaselineRow          ,
    getGridLayoutBaselineRow                ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutBaselineRow                   ,
#endif
    setGridLayoutBaselineRow                ,


-- ** columnHomogeneous #attr:columnHomogeneous#
-- | Whether all the columns in the grid have the same width.

#if defined(ENABLE_OVERLOADING)
    GridLayoutColumnHomogeneousPropertyInfo ,
#endif
    constructGridLayoutColumnHomogeneous    ,
    getGridLayoutColumnHomogeneous          ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutColumnHomogeneous             ,
#endif
    setGridLayoutColumnHomogeneous          ,


-- ** columnSpacing #attr:columnSpacing#
-- | The amount of space between to consecutive columns.

#if defined(ENABLE_OVERLOADING)
    GridLayoutColumnSpacingPropertyInfo     ,
#endif
    constructGridLayoutColumnSpacing        ,
    getGridLayoutColumnSpacing              ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutColumnSpacing                 ,
#endif
    setGridLayoutColumnSpacing              ,


-- ** rowHomogeneous #attr:rowHomogeneous#
-- | Whether all the rows in the grid have the same height.

#if defined(ENABLE_OVERLOADING)
    GridLayoutRowHomogeneousPropertyInfo    ,
#endif
    constructGridLayoutRowHomogeneous       ,
    getGridLayoutRowHomogeneous             ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutRowHomogeneous                ,
#endif
    setGridLayoutRowHomogeneous             ,


-- ** rowSpacing #attr:rowSpacing#
-- | The amount of space between to consecutive rows.

#if defined(ENABLE_OVERLOADING)
    GridLayoutRowSpacingPropertyInfo        ,
#endif
    constructGridLayoutRowSpacing           ,
    getGridLayoutRowSpacing                 ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutRowSpacing                    ,
#endif
    setGridLayoutRowSpacing                 ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager

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

instance GObject GridLayout where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_grid_layout_get_type
    

-- | Convert 'GridLayout' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue GridLayout where
    toGValue :: GridLayout -> IO GValue
toGValue o :: GridLayout
o = do
        GType
gtype <- IO GType
c_gtk_grid_layout_get_type
        GridLayout -> (Ptr GridLayout -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GridLayout
o (GType
-> (GValue -> Ptr GridLayout -> IO ())
-> Ptr GridLayout
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr GridLayout -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO GridLayout
fromGValue gv :: GValue
gv = do
        Ptr GridLayout
ptr <- GValue -> IO (Ptr GridLayout)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr GridLayout)
        (ManagedPtr GridLayout -> GridLayout)
-> Ptr GridLayout -> IO GridLayout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr GridLayout -> GridLayout
GridLayout Ptr GridLayout
ptr
        
    

-- | Type class for types which can be safely cast to `GridLayout`, for instance with `toGridLayout`.
class (GObject o, O.IsDescendantOf GridLayout o) => IsGridLayout o
instance (GObject o, O.IsDescendantOf GridLayout o) => IsGridLayout o

instance O.HasParentTypes GridLayout
type instance O.ParentTypes GridLayout = '[Gtk.LayoutManager.LayoutManager, GObject.Object.Object]

-- | Cast to `GridLayout`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toGridLayout :: (MonadIO m, IsGridLayout o) => o -> m GridLayout
toGridLayout :: o -> m GridLayout
toGridLayout = IO GridLayout -> m GridLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GridLayout -> m GridLayout)
-> (o -> IO GridLayout) -> o -> m GridLayout
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr GridLayout -> GridLayout) -> o -> IO GridLayout
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr GridLayout -> GridLayout
GridLayout

-- | A convenience alias for `Nothing` :: `Maybe` `GridLayout`.
noGridLayout :: Maybe GridLayout
noGridLayout :: Maybe GridLayout
noGridLayout = Maybe GridLayout
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveGridLayoutMethod (t :: Symbol) (o :: *) :: * where
    ResolveGridLayoutMethod "allocate" o = Gtk.LayoutManager.LayoutManagerAllocateMethodInfo
    ResolveGridLayoutMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGridLayoutMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGridLayoutMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGridLayoutMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGridLayoutMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGridLayoutMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGridLayoutMethod "layoutChanged" o = Gtk.LayoutManager.LayoutManagerLayoutChangedMethodInfo
    ResolveGridLayoutMethod "measure" o = Gtk.LayoutManager.LayoutManagerMeasureMethodInfo
    ResolveGridLayoutMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGridLayoutMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGridLayoutMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGridLayoutMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGridLayoutMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGridLayoutMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGridLayoutMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGridLayoutMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGridLayoutMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGridLayoutMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGridLayoutMethod "getBaselineRow" o = GridLayoutGetBaselineRowMethodInfo
    ResolveGridLayoutMethod "getColumnHomogeneous" o = GridLayoutGetColumnHomogeneousMethodInfo
    ResolveGridLayoutMethod "getColumnSpacing" o = GridLayoutGetColumnSpacingMethodInfo
    ResolveGridLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGridLayoutMethod "getLayoutChild" o = Gtk.LayoutManager.LayoutManagerGetLayoutChildMethodInfo
    ResolveGridLayoutMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGridLayoutMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGridLayoutMethod "getRequestMode" o = Gtk.LayoutManager.LayoutManagerGetRequestModeMethodInfo
    ResolveGridLayoutMethod "getRowBaselinePosition" o = GridLayoutGetRowBaselinePositionMethodInfo
    ResolveGridLayoutMethod "getRowHomogeneous" o = GridLayoutGetRowHomogeneousMethodInfo
    ResolveGridLayoutMethod "getRowSpacing" o = GridLayoutGetRowSpacingMethodInfo
    ResolveGridLayoutMethod "getWidget" o = Gtk.LayoutManager.LayoutManagerGetWidgetMethodInfo
    ResolveGridLayoutMethod "setBaselineRow" o = GridLayoutSetBaselineRowMethodInfo
    ResolveGridLayoutMethod "setColumnHomogeneous" o = GridLayoutSetColumnHomogeneousMethodInfo
    ResolveGridLayoutMethod "setColumnSpacing" o = GridLayoutSetColumnSpacingMethodInfo
    ResolveGridLayoutMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGridLayoutMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGridLayoutMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGridLayoutMethod "setRowBaselinePosition" o = GridLayoutSetRowBaselinePositionMethodInfo
    ResolveGridLayoutMethod "setRowHomogeneous" o = GridLayoutSetRowHomogeneousMethodInfo
    ResolveGridLayoutMethod "setRowSpacing" o = GridLayoutSetRowSpacingMethodInfo
    ResolveGridLayoutMethod l o = O.MethodResolutionFailed l o

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

#endif

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

-- | Get the value of the “@baseline-row@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gridLayout #baselineRow
-- @
getGridLayoutBaselineRow :: (MonadIO m, IsGridLayout o) => o -> m Int32
getGridLayoutBaselineRow :: o -> m Int32
getGridLayoutBaselineRow obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "baseline-row"

-- | Set the value of the “@baseline-row@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayout [ #baselineRow 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutBaselineRow :: (MonadIO m, IsGridLayout o) => o -> Int32 -> m ()
setGridLayoutBaselineRow :: o -> Int32 -> m ()
setGridLayoutBaselineRow obj :: o
obj val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "baseline-row" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@baseline-row@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutBaselineRow :: (IsGridLayout o) => Int32 -> IO (GValueConstruct o)
constructGridLayoutBaselineRow :: Int32 -> IO (GValueConstruct o)
constructGridLayoutBaselineRow val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "baseline-row" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutBaselineRowPropertyInfo
instance AttrInfo GridLayoutBaselineRowPropertyInfo where
    type AttrAllowedOps GridLayoutBaselineRowPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutBaselineRowPropertyInfo = IsGridLayout
    type AttrSetTypeConstraint GridLayoutBaselineRowPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutBaselineRowPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutBaselineRowPropertyInfo = Int32
    type AttrGetType GridLayoutBaselineRowPropertyInfo = Int32
    type AttrLabel GridLayoutBaselineRowPropertyInfo = "baseline-row"
    type AttrOrigin GridLayoutBaselineRowPropertyInfo = GridLayout
    attrGet = getGridLayoutBaselineRow
    attrSet = setGridLayoutBaselineRow
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutBaselineRow
    attrClear = undefined
#endif

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

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

-- | Set the value of the “@column-homogeneous@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayout [ #columnHomogeneous 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutColumnHomogeneous :: (MonadIO m, IsGridLayout o) => o -> Bool -> m ()
setGridLayoutColumnHomogeneous :: o -> Bool -> m ()
setGridLayoutColumnHomogeneous obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "column-homogeneous" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@column-homogeneous@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutColumnHomogeneous :: (IsGridLayout o) => Bool -> IO (GValueConstruct o)
constructGridLayoutColumnHomogeneous :: Bool -> IO (GValueConstruct o)
constructGridLayoutColumnHomogeneous val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "column-homogeneous" Bool
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutColumnHomogeneousPropertyInfo
instance AttrInfo GridLayoutColumnHomogeneousPropertyInfo where
    type AttrAllowedOps GridLayoutColumnHomogeneousPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutColumnHomogeneousPropertyInfo = IsGridLayout
    type AttrSetTypeConstraint GridLayoutColumnHomogeneousPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint GridLayoutColumnHomogeneousPropertyInfo = (~) Bool
    type AttrTransferType GridLayoutColumnHomogeneousPropertyInfo = Bool
    type AttrGetType GridLayoutColumnHomogeneousPropertyInfo = Bool
    type AttrLabel GridLayoutColumnHomogeneousPropertyInfo = "column-homogeneous"
    type AttrOrigin GridLayoutColumnHomogeneousPropertyInfo = GridLayout
    attrGet = getGridLayoutColumnHomogeneous
    attrSet = setGridLayoutColumnHomogeneous
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutColumnHomogeneous
    attrClear = undefined
#endif

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

-- | Get the value of the “@column-spacing@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gridLayout #columnSpacing
-- @
getGridLayoutColumnSpacing :: (MonadIO m, IsGridLayout o) => o -> m Int32
getGridLayoutColumnSpacing :: o -> m Int32
getGridLayoutColumnSpacing obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "column-spacing"

-- | Set the value of the “@column-spacing@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayout [ #columnSpacing 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutColumnSpacing :: (MonadIO m, IsGridLayout o) => o -> Int32 -> m ()
setGridLayoutColumnSpacing :: o -> Int32 -> m ()
setGridLayoutColumnSpacing obj :: o
obj val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "column-spacing" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@column-spacing@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutColumnSpacing :: (IsGridLayout o) => Int32 -> IO (GValueConstruct o)
constructGridLayoutColumnSpacing :: Int32 -> IO (GValueConstruct o)
constructGridLayoutColumnSpacing val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "column-spacing" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutColumnSpacingPropertyInfo
instance AttrInfo GridLayoutColumnSpacingPropertyInfo where
    type AttrAllowedOps GridLayoutColumnSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutColumnSpacingPropertyInfo = IsGridLayout
    type AttrSetTypeConstraint GridLayoutColumnSpacingPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutColumnSpacingPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutColumnSpacingPropertyInfo = Int32
    type AttrGetType GridLayoutColumnSpacingPropertyInfo = Int32
    type AttrLabel GridLayoutColumnSpacingPropertyInfo = "column-spacing"
    type AttrOrigin GridLayoutColumnSpacingPropertyInfo = GridLayout
    attrGet = getGridLayoutColumnSpacing
    attrSet = setGridLayoutColumnSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutColumnSpacing
    attrClear = undefined
#endif

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

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

-- | Set the value of the “@row-homogeneous@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayout [ #rowHomogeneous 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutRowHomogeneous :: (MonadIO m, IsGridLayout o) => o -> Bool -> m ()
setGridLayoutRowHomogeneous :: o -> Bool -> m ()
setGridLayoutRowHomogeneous obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "row-homogeneous" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@row-homogeneous@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutRowHomogeneous :: (IsGridLayout o) => Bool -> IO (GValueConstruct o)
constructGridLayoutRowHomogeneous :: Bool -> IO (GValueConstruct o)
constructGridLayoutRowHomogeneous val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "row-homogeneous" Bool
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutRowHomogeneousPropertyInfo
instance AttrInfo GridLayoutRowHomogeneousPropertyInfo where
    type AttrAllowedOps GridLayoutRowHomogeneousPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutRowHomogeneousPropertyInfo = IsGridLayout
    type AttrSetTypeConstraint GridLayoutRowHomogeneousPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint GridLayoutRowHomogeneousPropertyInfo = (~) Bool
    type AttrTransferType GridLayoutRowHomogeneousPropertyInfo = Bool
    type AttrGetType GridLayoutRowHomogeneousPropertyInfo = Bool
    type AttrLabel GridLayoutRowHomogeneousPropertyInfo = "row-homogeneous"
    type AttrOrigin GridLayoutRowHomogeneousPropertyInfo = GridLayout
    attrGet = getGridLayoutRowHomogeneous
    attrSet = setGridLayoutRowHomogeneous
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutRowHomogeneous
    attrClear = undefined
#endif

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

-- | Get the value of the “@row-spacing@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gridLayout #rowSpacing
-- @
getGridLayoutRowSpacing :: (MonadIO m, IsGridLayout o) => o -> m Int32
getGridLayoutRowSpacing :: o -> m Int32
getGridLayoutRowSpacing obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "row-spacing"

-- | Set the value of the “@row-spacing@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayout [ #rowSpacing 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutRowSpacing :: (MonadIO m, IsGridLayout o) => o -> Int32 -> m ()
setGridLayoutRowSpacing :: o -> Int32 -> m ()
setGridLayoutRowSpacing obj :: o
obj val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "row-spacing" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@row-spacing@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutRowSpacing :: (IsGridLayout o) => Int32 -> IO (GValueConstruct o)
constructGridLayoutRowSpacing :: Int32 -> IO (GValueConstruct o)
constructGridLayoutRowSpacing val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "row-spacing" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutRowSpacingPropertyInfo
instance AttrInfo GridLayoutRowSpacingPropertyInfo where
    type AttrAllowedOps GridLayoutRowSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutRowSpacingPropertyInfo = IsGridLayout
    type AttrSetTypeConstraint GridLayoutRowSpacingPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutRowSpacingPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutRowSpacingPropertyInfo = Int32
    type AttrGetType GridLayoutRowSpacingPropertyInfo = Int32
    type AttrLabel GridLayoutRowSpacingPropertyInfo = "row-spacing"
    type AttrOrigin GridLayoutRowSpacingPropertyInfo = GridLayout
    attrGet = getGridLayoutRowSpacing
    attrSet = setGridLayoutRowSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutRowSpacing
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GridLayout
type instance O.AttributeList GridLayout = GridLayoutAttributeList
type GridLayoutAttributeList = ('[ '("baselineRow", GridLayoutBaselineRowPropertyInfo), '("columnHomogeneous", GridLayoutColumnHomogeneousPropertyInfo), '("columnSpacing", GridLayoutColumnSpacingPropertyInfo), '("rowHomogeneous", GridLayoutRowHomogeneousPropertyInfo), '("rowSpacing", GridLayoutRowSpacingPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
gridLayoutBaselineRow :: AttrLabelProxy "baselineRow"
gridLayoutBaselineRow = AttrLabelProxy

gridLayoutColumnHomogeneous :: AttrLabelProxy "columnHomogeneous"
gridLayoutColumnHomogeneous = AttrLabelProxy

gridLayoutColumnSpacing :: AttrLabelProxy "columnSpacing"
gridLayoutColumnSpacing = AttrLabelProxy

gridLayoutRowHomogeneous :: AttrLabelProxy "rowHomogeneous"
gridLayoutRowHomogeneous = AttrLabelProxy

gridLayoutRowSpacing :: AttrLabelProxy "rowSpacing"
gridLayoutRowSpacing = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "gtk_grid_layout_new" gtk_grid_layout_new :: 
    IO (Ptr GridLayout)

-- | Creates a new t'GI.Gtk.Objects.GridLayout.GridLayout'.
gridLayoutNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m GridLayout
    -- ^ __Returns:__ the newly created t'GI.Gtk.Objects.GridLayout.GridLayout'
gridLayoutNew :: m GridLayout
gridLayoutNew  = IO GridLayout -> m GridLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GridLayout -> m GridLayout) -> IO GridLayout -> m GridLayout
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
result <- IO (Ptr GridLayout)
gtk_grid_layout_new
    Text -> Ptr GridLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "gridLayoutNew" Ptr GridLayout
result
    GridLayout
result' <- ((ManagedPtr GridLayout -> GridLayout)
-> Ptr GridLayout -> IO GridLayout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr GridLayout -> GridLayout
GridLayout) Ptr GridLayout
result
    GridLayout -> IO GridLayout
forall (m :: * -> *) a. Monad m => a -> m a
return GridLayout
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method GridLayout::get_baseline_row
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "grid"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayout" , 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_get_baseline_row" gtk_grid_layout_get_baseline_row :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    IO Int32

-- | Retrieves the row set with 'GI.Gtk.Objects.GridLayout.gridLayoutSetBaselineRow'.
gridLayoutGetBaselineRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> m Int32
    -- ^ __Returns:__ the global baseline row
gridLayoutGetBaselineRow :: a -> m Int32
gridLayoutGetBaselineRow grid :: a
grid = 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 GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Int32
result <- Ptr GridLayout -> IO Int32
gtk_grid_layout_get_baseline_row Ptr GridLayout
grid'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutGetBaselineRowMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutGetBaselineRowMethodInfo a signature where
    overloadedMethod = gridLayoutGetBaselineRow

#endif

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

foreign import ccall "gtk_grid_layout_get_column_homogeneous" gtk_grid_layout_get_column_homogeneous :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    IO CInt

-- | Checks whether all columns of /@grid@/ should have the same width.
gridLayoutGetColumnHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the columns are homogeneous, and 'P.False' otherwise
gridLayoutGetColumnHomogeneous :: a -> m Bool
gridLayoutGetColumnHomogeneous grid :: a
grid = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    CInt
result <- Ptr GridLayout -> IO CInt
gtk_grid_layout_get_column_homogeneous Ptr GridLayout
grid'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GridLayoutGetColumnHomogeneousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutGetColumnHomogeneousMethodInfo a signature where
    overloadedMethod = gridLayoutGetColumnHomogeneous

#endif

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

foreign import ccall "gtk_grid_layout_get_column_spacing" gtk_grid_layout_get_column_spacing :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    IO Word32

-- | Retrieves the spacing set with 'GI.Gtk.Objects.GridLayout.gridLayoutSetColumnSpacing'.
gridLayoutGetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> m Word32
    -- ^ __Returns:__ the spacing between consecutive columns
gridLayoutGetColumnSpacing :: a -> m Word32
gridLayoutGetColumnSpacing grid :: a
grid = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Word32
result <- Ptr GridLayout -> IO Word32
gtk_grid_layout_get_column_spacing Ptr GridLayout
grid'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutGetColumnSpacingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutGetColumnSpacingMethodInfo a signature where
    overloadedMethod = gridLayoutGetColumnSpacing

#endif

-- method GridLayout::get_row_baseline_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "grid"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayout" , 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 "a row index" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "BaselinePosition" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_get_row_baseline_position" gtk_grid_layout_get_row_baseline_position :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    Int32 ->                                -- row : TBasicType TInt
    IO CUInt

-- | Returns the baseline position of /@row@/ as set by
-- 'GI.Gtk.Objects.GridLayout.gridLayoutSetRowBaselinePosition', or the default value
-- of 'GI.Gtk.Enums.BaselinePositionCenter'.
gridLayoutGetRowBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> Int32
    -- ^ /@row@/: a row index
    -> m Gtk.Enums.BaselinePosition
    -- ^ __Returns:__ the baseline position of /@row@/
gridLayoutGetRowBaselinePosition :: a -> Int32 -> m BaselinePosition
gridLayoutGetRowBaselinePosition grid :: a
grid row :: Int32
row = IO BaselinePosition -> m BaselinePosition
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BaselinePosition -> m BaselinePosition)
-> IO BaselinePosition -> m BaselinePosition
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    CUInt
result <- Ptr GridLayout -> Int32 -> IO CUInt
gtk_grid_layout_get_row_baseline_position Ptr GridLayout
grid' Int32
row
    let result' :: BaselinePosition
result' = (Int -> BaselinePosition
forall a. Enum a => Int -> a
toEnum (Int -> BaselinePosition)
-> (CUInt -> Int) -> CUInt -> BaselinePosition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    BaselinePosition -> IO BaselinePosition
forall (m :: * -> *) a. Monad m => a -> m a
return BaselinePosition
result'

#if defined(ENABLE_OVERLOADING)
data GridLayoutGetRowBaselinePositionMethodInfo
instance (signature ~ (Int32 -> m Gtk.Enums.BaselinePosition), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutGetRowBaselinePositionMethodInfo a signature where
    overloadedMethod = gridLayoutGetRowBaselinePosition

#endif

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

foreign import ccall "gtk_grid_layout_get_row_homogeneous" gtk_grid_layout_get_row_homogeneous :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    IO CInt

-- | Checks whether all rows of /@grid@/ should have the same height.
gridLayoutGetRowHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the rows are homogeneous, and 'P.False' otherwise
gridLayoutGetRowHomogeneous :: a -> m Bool
gridLayoutGetRowHomogeneous grid :: a
grid = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    CInt
result <- Ptr GridLayout -> IO CInt
gtk_grid_layout_get_row_homogeneous Ptr GridLayout
grid'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GridLayoutGetRowHomogeneousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutGetRowHomogeneousMethodInfo a signature where
    overloadedMethod = gridLayoutGetRowHomogeneous

#endif

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

foreign import ccall "gtk_grid_layout_get_row_spacing" gtk_grid_layout_get_row_spacing :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    IO Word32

-- | Retrieves the spacing set with 'GI.Gtk.Objects.GridLayout.gridLayoutSetRowSpacing'.
gridLayoutGetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> m Word32
    -- ^ __Returns:__ the spacing between consecutive rows
gridLayoutGetRowSpacing :: a -> m Word32
gridLayoutGetRowSpacing grid :: a
grid = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Word32
result <- Ptr GridLayout -> IO Word32
gtk_grid_layout_get_row_spacing Ptr GridLayout
grid'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutGetRowSpacingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutGetRowSpacingMethodInfo a signature where
    overloadedMethod = gridLayoutGetRowSpacing

#endif

-- method GridLayout::set_baseline_row
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "grid"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayout" , 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 index" , 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_set_baseline_row" gtk_grid_layout_set_baseline_row :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    Int32 ->                                -- row : TBasicType TInt
    IO ()

-- | Sets which row defines the global baseline for the entire grid.
-- 
-- Each row in the grid can have its own local baseline, but only
-- one of those is global, meaning it will be the baseline in the
-- parent of the /@grid@/.
gridLayoutSetBaselineRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> Int32
    -- ^ /@row@/: the row index
    -> m ()
gridLayoutSetBaselineRow :: a -> Int32 -> m ()
gridLayoutSetBaselineRow grid :: a
grid row :: 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 GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr GridLayout -> Int32 -> IO ()
gtk_grid_layout_set_baseline_row Ptr GridLayout
grid' Int32
row
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutSetBaselineRowMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutSetBaselineRowMethodInfo a signature where
    overloadedMethod = gridLayoutSetBaselineRow

#endif

-- method GridLayout::set_column_homogeneous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "grid"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "homogeneous"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to make columns homogeneous"
--                 , 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_set_column_homogeneous" gtk_grid_layout_set_column_homogeneous :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    CInt ->                                 -- homogeneous : TBasicType TBoolean
    IO ()

-- | Sets whether all columns of /@grid@/ should have the same width.
gridLayoutSetColumnHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> Bool
    -- ^ /@homogeneous@/: 'P.True' to make columns homogeneous
    -> m ()
gridLayoutSetColumnHomogeneous :: a -> Bool -> m ()
gridLayoutSetColumnHomogeneous grid :: a
grid homogeneous :: Bool
homogeneous = 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 GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    let homogeneous' :: CInt
homogeneous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
homogeneous
    Ptr GridLayout -> CInt -> IO ()
gtk_grid_layout_set_column_homogeneous Ptr GridLayout
grid' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutSetColumnHomogeneousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutSetColumnHomogeneousMethodInfo a signature where
    overloadedMethod = gridLayoutSetColumnHomogeneous

#endif

-- method GridLayout::set_column_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "grid"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spacing"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the amount of space between columns, in pixels"
--                 , 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_set_column_spacing" gtk_grid_layout_set_column_spacing :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    Word32 ->                               -- spacing : TBasicType TUInt
    IO ()

-- | Sets the amount of space to insert between consecutive columns.
gridLayoutSetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> Word32
    -- ^ /@spacing@/: the amount of space between columns, in pixels
    -> m ()
gridLayoutSetColumnSpacing :: a -> Word32 -> m ()
gridLayoutSetColumnSpacing grid :: a
grid spacing :: Word32
spacing = 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 GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr GridLayout -> Word32 -> IO ()
gtk_grid_layout_set_column_spacing Ptr GridLayout
grid' Word32
spacing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutSetColumnSpacingMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutSetColumnSpacingMethodInfo a signature where
    overloadedMethod = gridLayoutSetColumnSpacing

#endif

-- method GridLayout::set_row_baseline_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "grid"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayout" , 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 "a row index" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BaselinePosition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkBaselinePosition"
--                 , 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_set_row_baseline_position" gtk_grid_layout_set_row_baseline_position :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    Int32 ->                                -- row : TBasicType TInt
    CUInt ->                                -- pos : TInterface (Name {namespace = "Gtk", name = "BaselinePosition"})
    IO ()

-- | Sets how the baseline should be positioned on /@row@/ of the
-- grid, in case that row is assigned more space than is requested.
gridLayoutSetRowBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> Int32
    -- ^ /@row@/: a row index
    -> Gtk.Enums.BaselinePosition
    -- ^ /@pos@/: a t'GI.Gtk.Enums.BaselinePosition'
    -> m ()
gridLayoutSetRowBaselinePosition :: a -> Int32 -> BaselinePosition -> m ()
gridLayoutSetRowBaselinePosition grid :: a
grid row :: Int32
row pos :: BaselinePosition
pos = 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 GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    let pos' :: CUInt
pos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (BaselinePosition -> Int) -> BaselinePosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BaselinePosition -> Int
forall a. Enum a => a -> Int
fromEnum) BaselinePosition
pos
    Ptr GridLayout -> Int32 -> CUInt -> IO ()
gtk_grid_layout_set_row_baseline_position Ptr GridLayout
grid' Int32
row CUInt
pos'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutSetRowBaselinePositionMethodInfo
instance (signature ~ (Int32 -> Gtk.Enums.BaselinePosition -> m ()), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutSetRowBaselinePositionMethodInfo a signature where
    overloadedMethod = gridLayoutSetRowBaselinePosition

#endif

-- method GridLayout::set_row_homogeneous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "grid"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "homogeneous"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to make rows homogeneous"
--                 , 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_set_row_homogeneous" gtk_grid_layout_set_row_homogeneous :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    CInt ->                                 -- homogeneous : TBasicType TBoolean
    IO ()

-- | Sets whether all rows of /@grid@/ should have the same height.
gridLayoutSetRowHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> Bool
    -- ^ /@homogeneous@/: 'P.True' to make rows homogeneous
    -> m ()
gridLayoutSetRowHomogeneous :: a -> Bool -> m ()
gridLayoutSetRowHomogeneous grid :: a
grid homogeneous :: Bool
homogeneous = 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 GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    let homogeneous' :: CInt
homogeneous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
homogeneous
    Ptr GridLayout -> CInt -> IO ()
gtk_grid_layout_set_row_homogeneous Ptr GridLayout
grid' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutSetRowHomogeneousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutSetRowHomogeneousMethodInfo a signature where
    overloadedMethod = gridLayoutSetRowHomogeneous

#endif

-- method GridLayout::set_row_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "grid"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spacing"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the amount of space between rows, in pixels"
--                 , 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_set_row_spacing" gtk_grid_layout_set_row_spacing :: 
    Ptr GridLayout ->                       -- grid : TInterface (Name {namespace = "Gtk", name = "GridLayout"})
    Word32 ->                               -- spacing : TBasicType TUInt
    IO ()

-- | Sets the amount of space to insert between consecutive rows.
gridLayoutSetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@grid@/: a t'GI.Gtk.Objects.GridLayout.GridLayout'
    -> Word32
    -- ^ /@spacing@/: the amount of space between rows, in pixels
    -> m ()
gridLayoutSetRowSpacing :: a -> Word32 -> m ()
gridLayoutSetRowSpacing grid :: a
grid spacing :: Word32
spacing = 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 GridLayout
grid' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr GridLayout -> Word32 -> IO ()
gtk_grid_layout_set_row_spacing Ptr GridLayout
grid' Word32
spacing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutSetRowSpacingMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsGridLayout a) => O.MethodInfo GridLayoutSetRowSpacingMethodInfo a signature where
    overloadedMethod = gridLayoutSetRowSpacing

#endif