{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Clutter.Objects.GridLayout.GridLayout' structure contains only private data
-- and should be accessed using the provided API
-- 
-- /Since: 1.12/

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

module GI.Clutter.Objects.GridLayout
    ( 

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


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [allocate]("GI.Clutter.Objects.LayoutManager#g:method:allocate"), [attach]("GI.Clutter.Objects.GridLayout#g:method:attach"), [attachNextTo]("GI.Clutter.Objects.GridLayout#g:method:attachNextTo"), [beginAnimation]("GI.Clutter.Objects.LayoutManager#g:method:beginAnimation"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childGetProperty]("GI.Clutter.Objects.LayoutManager#g:method:childGetProperty"), [childSetProperty]("GI.Clutter.Objects.LayoutManager#g:method:childSetProperty"), [endAnimation]("GI.Clutter.Objects.LayoutManager#g:method:endAnimation"), [findChildProperty]("GI.Clutter.Objects.LayoutManager#g:method:findChildProperty"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [insertColumn]("GI.Clutter.Objects.GridLayout#g:method:insertColumn"), [insertNextTo]("GI.Clutter.Objects.GridLayout#g:method:insertNextTo"), [insertRow]("GI.Clutter.Objects.GridLayout#g:method:insertRow"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [layoutChanged]("GI.Clutter.Objects.LayoutManager#g:method:layoutChanged"), [listChildProperties]("GI.Clutter.Objects.LayoutManager#g:method:listChildProperties"), [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
-- [getAnimationProgress]("GI.Clutter.Objects.LayoutManager#g:method:getAnimationProgress"), [getChildAt]("GI.Clutter.Objects.GridLayout#g:method:getChildAt"), [getChildMeta]("GI.Clutter.Objects.LayoutManager#g:method:getChildMeta"), [getColumnHomogeneous]("GI.Clutter.Objects.GridLayout#g:method:getColumnHomogeneous"), [getColumnSpacing]("GI.Clutter.Objects.GridLayout#g:method:getColumnSpacing"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getOrientation]("GI.Clutter.Objects.GridLayout#g:method:getOrientation"), [getPreferredHeight]("GI.Clutter.Objects.LayoutManager#g:method:getPreferredHeight"), [getPreferredWidth]("GI.Clutter.Objects.LayoutManager#g:method:getPreferredWidth"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRowHomogeneous]("GI.Clutter.Objects.GridLayout#g:method:getRowHomogeneous"), [getRowSpacing]("GI.Clutter.Objects.GridLayout#g:method:getRowSpacing").
-- 
-- ==== Setters
-- [setColumnHomogeneous]("GI.Clutter.Objects.GridLayout#g:method:setColumnHomogeneous"), [setColumnSpacing]("GI.Clutter.Objects.GridLayout#g:method:setColumnSpacing"), [setContainer]("GI.Clutter.Objects.LayoutManager#g:method:setContainer"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setOrientation]("GI.Clutter.Objects.GridLayout#g:method:setOrientation"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRowHomogeneous]("GI.Clutter.Objects.GridLayout#g:method:setRowHomogeneous"), [setRowSpacing]("GI.Clutter.Objects.GridLayout#g:method:setRowSpacing").

#if defined(ENABLE_OVERLOADING)
    ResolveGridLayoutMethod                 ,
#endif

-- ** attach #method:attach#

#if defined(ENABLE_OVERLOADING)
    GridLayoutAttachMethodInfo              ,
#endif
    gridLayoutAttach                        ,


-- ** attachNextTo #method:attachNextTo#

#if defined(ENABLE_OVERLOADING)
    GridLayoutAttachNextToMethodInfo        ,
#endif
    gridLayoutAttachNextTo                  ,


-- ** getChildAt #method:getChildAt#

#if defined(ENABLE_OVERLOADING)
    GridLayoutGetChildAtMethodInfo          ,
#endif
    gridLayoutGetChildAt                    ,


-- ** getColumnHomogeneous #method:getColumnHomogeneous#

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


-- ** getColumnSpacing #method:getColumnSpacing#

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


-- ** getOrientation #method:getOrientation#

#if defined(ENABLE_OVERLOADING)
    GridLayoutGetOrientationMethodInfo      ,
#endif
    gridLayoutGetOrientation                ,


-- ** getRowHomogeneous #method:getRowHomogeneous#

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


-- ** getRowSpacing #method:getRowSpacing#

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


-- ** insertColumn #method:insertColumn#

#if defined(ENABLE_OVERLOADING)
    GridLayoutInsertColumnMethodInfo        ,
#endif
    gridLayoutInsertColumn                  ,


-- ** insertNextTo #method:insertNextTo#

#if defined(ENABLE_OVERLOADING)
    GridLayoutInsertNextToMethodInfo        ,
#endif
    gridLayoutInsertNextTo                  ,


-- ** insertRow #method:insertRow#

#if defined(ENABLE_OVERLOADING)
    GridLayoutInsertRowMethodInfo           ,
#endif
    gridLayoutInsertRow                     ,


-- ** new #method:new#

    gridLayoutNew                           ,


-- ** setColumnHomogeneous #method:setColumnHomogeneous#

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


-- ** setColumnSpacing #method:setColumnSpacing#

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


-- ** setOrientation #method:setOrientation#

#if defined(ENABLE_OVERLOADING)
    GridLayoutSetOrientationMethodInfo      ,
#endif
    gridLayoutSetOrientation                ,


-- ** setRowHomogeneous #method:setRowHomogeneous#

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


-- ** setRowSpacing #method:setRowSpacing#

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




 -- * Properties


-- ** columnHomogeneous #attr:columnHomogeneous#
-- | Whether all columns of the layout should have the same width
-- 
-- /Since: 1.12/

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


-- ** columnSpacing #attr:columnSpacing#
-- | The amount of space in pixels between two consecutive columns
-- 
-- /Since: 1.12/

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


-- ** orientation #attr:orientation#
-- | The orientation of the layout, either horizontal or vertical
-- 
-- /Since: 1.12/

#if defined(ENABLE_OVERLOADING)
    GridLayoutOrientationPropertyInfo       ,
#endif
    constructGridLayoutOrientation          ,
    getGridLayoutOrientation                ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutOrientation                   ,
#endif
    setGridLayoutOrientation                ,


-- ** rowHomogeneous #attr:rowHomogeneous#
-- | Whether all rows of the layout should have the same height
-- 
-- /Since: 1.12/

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


-- ** rowSpacing #attr:rowSpacing#
-- | The amount of space in pixels between two consecutive rows
-- 
-- /Since: 1.12/

#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

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

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

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

foreign import ccall "clutter_grid_layout_get_type"
    c_clutter_grid_layout_get_type :: IO B.Types.GType

instance B.Types.TypedObject GridLayout where
    glibType :: IO GType
glibType = IO GType
c_clutter_grid_layout_get_type

instance B.Types.GObject GridLayout

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

instance O.HasParentTypes GridLayout
type instance O.ParentTypes GridLayout = '[Clutter.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 :: (MIO.MonadIO m, IsGridLayout o) => o -> m GridLayout
toGridLayout :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> m GridLayout
toGridLayout = IO GridLayout -> m GridLayout
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr GridLayout -> GridLayout
GridLayout

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

#if defined(ENABLE_OVERLOADING)
type family ResolveGridLayoutMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveGridLayoutMethod "allocate" o = Clutter.LayoutManager.LayoutManagerAllocateMethodInfo
    ResolveGridLayoutMethod "attach" o = GridLayoutAttachMethodInfo
    ResolveGridLayoutMethod "attachNextTo" o = GridLayoutAttachNextToMethodInfo
    ResolveGridLayoutMethod "beginAnimation" o = Clutter.LayoutManager.LayoutManagerBeginAnimationMethodInfo
    ResolveGridLayoutMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGridLayoutMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGridLayoutMethod "childGetProperty" o = Clutter.LayoutManager.LayoutManagerChildGetPropertyMethodInfo
    ResolveGridLayoutMethod "childSetProperty" o = Clutter.LayoutManager.LayoutManagerChildSetPropertyMethodInfo
    ResolveGridLayoutMethod "endAnimation" o = Clutter.LayoutManager.LayoutManagerEndAnimationMethodInfo
    ResolveGridLayoutMethod "findChildProperty" o = Clutter.LayoutManager.LayoutManagerFindChildPropertyMethodInfo
    ResolveGridLayoutMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGridLayoutMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGridLayoutMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGridLayoutMethod "insertColumn" o = GridLayoutInsertColumnMethodInfo
    ResolveGridLayoutMethod "insertNextTo" o = GridLayoutInsertNextToMethodInfo
    ResolveGridLayoutMethod "insertRow" o = GridLayoutInsertRowMethodInfo
    ResolveGridLayoutMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGridLayoutMethod "layoutChanged" o = Clutter.LayoutManager.LayoutManagerLayoutChangedMethodInfo
    ResolveGridLayoutMethod "listChildProperties" o = Clutter.LayoutManager.LayoutManagerListChildPropertiesMethodInfo
    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 "getAnimationProgress" o = Clutter.LayoutManager.LayoutManagerGetAnimationProgressMethodInfo
    ResolveGridLayoutMethod "getChildAt" o = GridLayoutGetChildAtMethodInfo
    ResolveGridLayoutMethod "getChildMeta" o = Clutter.LayoutManager.LayoutManagerGetChildMetaMethodInfo
    ResolveGridLayoutMethod "getColumnHomogeneous" o = GridLayoutGetColumnHomogeneousMethodInfo
    ResolveGridLayoutMethod "getColumnSpacing" o = GridLayoutGetColumnSpacingMethodInfo
    ResolveGridLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGridLayoutMethod "getOrientation" o = GridLayoutGetOrientationMethodInfo
    ResolveGridLayoutMethod "getPreferredHeight" o = Clutter.LayoutManager.LayoutManagerGetPreferredHeightMethodInfo
    ResolveGridLayoutMethod "getPreferredWidth" o = Clutter.LayoutManager.LayoutManagerGetPreferredWidthMethodInfo
    ResolveGridLayoutMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGridLayoutMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGridLayoutMethod "getRowHomogeneous" o = GridLayoutGetRowHomogeneousMethodInfo
    ResolveGridLayoutMethod "getRowSpacing" o = GridLayoutGetRowSpacingMethodInfo
    ResolveGridLayoutMethod "setColumnHomogeneous" o = GridLayoutSetColumnHomogeneousMethodInfo
    ResolveGridLayoutMethod "setColumnSpacing" o = GridLayoutSetColumnSpacingMethodInfo
    ResolveGridLayoutMethod "setContainer" o = Clutter.LayoutManager.LayoutManagerSetContainerMethodInfo
    ResolveGridLayoutMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGridLayoutMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGridLayoutMethod "setOrientation" o = GridLayoutSetOrientationMethodInfo
    ResolveGridLayoutMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGridLayoutMethod "setRowHomogeneous" o = GridLayoutSetRowHomogeneousMethodInfo
    ResolveGridLayoutMethod "setRowSpacing" o = GridLayoutSetRowSpacingMethodInfo
    ResolveGridLayoutMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveGridLayoutMethod t GridLayout, O.OverloadedMethod 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

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

#endif

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

#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 :: forall (m :: * -> *) o. (MonadIO m, IsGridLayout o) => o -> m Bool
getGridLayoutColumnHomogeneous o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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 :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> Bool -> m ()
setGridLayoutColumnHomogeneous o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"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, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructGridLayoutColumnHomogeneous :: forall o (m :: * -> *).
(IsGridLayout o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructGridLayoutColumnHomogeneous Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.columnHomogeneous"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#g:attr:columnHomogeneous"
        })
#endif

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

-- | 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 Word32
getGridLayoutColumnSpacing :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> m Word32
getGridLayoutColumnSpacing o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"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 -> Word32 -> m ()
setGridLayoutColumnSpacing :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> Word32 -> m ()
setGridLayoutColumnSpacing o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"column-spacing" Word32
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, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructGridLayoutColumnSpacing :: forall o (m :: * -> *).
(IsGridLayout o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructGridLayoutColumnSpacing Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"column-spacing" Word32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutColumnSpacingPropertyInfo
instance AttrInfo GridLayoutColumnSpacingPropertyInfo where
    type AttrAllowedOps GridLayoutColumnSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutColumnSpacingPropertyInfo = IsGridLayout
    type AttrSetTypeConstraint GridLayoutColumnSpacingPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint GridLayoutColumnSpacingPropertyInfo = (~) Word32
    type AttrTransferType GridLayoutColumnSpacingPropertyInfo = Word32
    type AttrGetType GridLayoutColumnSpacingPropertyInfo = Word32
    type AttrLabel GridLayoutColumnSpacingPropertyInfo = "column-spacing"
    type AttrOrigin GridLayoutColumnSpacingPropertyInfo = GridLayout
    attrGet = getGridLayoutColumnSpacing
    attrSet = setGridLayoutColumnSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutColumnSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.columnSpacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#g:attr:columnSpacing"
        })
#endif

-- VVV Prop "orientation"
   -- Type: TInterface (Name {namespace = "Clutter", name = "Orientation"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@orientation@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gridLayout #orientation
-- @
getGridLayoutOrientation :: (MonadIO m, IsGridLayout o) => o -> m Clutter.Enums.Orientation
getGridLayoutOrientation :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> m Orientation
getGridLayoutOrientation o
obj = IO Orientation -> m Orientation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Orientation -> m Orientation)
-> IO Orientation -> m Orientation
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Orientation
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"orientation"

-- | Set the value of the “@orientation@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayout [ #orientation 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutOrientation :: (MonadIO m, IsGridLayout o) => o -> Clutter.Enums.Orientation -> m ()
setGridLayoutOrientation :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> Orientation -> m ()
setGridLayoutOrientation o
obj Orientation
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Orientation -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"orientation" Orientation
val

-- | Construct a `GValueConstruct` with valid value for the “@orientation@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutOrientation :: (IsGridLayout o, MIO.MonadIO m) => Clutter.Enums.Orientation -> m (GValueConstruct o)
constructGridLayoutOrientation :: forall o (m :: * -> *).
(IsGridLayout o, MonadIO m) =>
Orientation -> m (GValueConstruct o)
constructGridLayoutOrientation Orientation
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Orientation -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"orientation" Orientation
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutOrientationPropertyInfo
instance AttrInfo GridLayoutOrientationPropertyInfo where
    type AttrAllowedOps GridLayoutOrientationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutOrientationPropertyInfo = IsGridLayout
    type AttrSetTypeConstraint GridLayoutOrientationPropertyInfo = (~) Clutter.Enums.Orientation
    type AttrTransferTypeConstraint GridLayoutOrientationPropertyInfo = (~) Clutter.Enums.Orientation
    type AttrTransferType GridLayoutOrientationPropertyInfo = Clutter.Enums.Orientation
    type AttrGetType GridLayoutOrientationPropertyInfo = Clutter.Enums.Orientation
    type AttrLabel GridLayoutOrientationPropertyInfo = "orientation"
    type AttrOrigin GridLayoutOrientationPropertyInfo = GridLayout
    attrGet = getGridLayoutOrientation
    attrSet = setGridLayoutOrientation
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutOrientation
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.orientation"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#g:attr:orientation"
        })
#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 :: forall (m :: * -> *) o. (MonadIO m, IsGridLayout o) => o -> m Bool
getGridLayoutRowHomogeneous o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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 :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> Bool -> m ()
setGridLayoutRowHomogeneous o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"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, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructGridLayoutRowHomogeneous :: forall o (m :: * -> *).
(IsGridLayout o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructGridLayoutRowHomogeneous Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.rowHomogeneous"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#g:attr:rowHomogeneous"
        })
#endif

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

-- | 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 Word32
getGridLayoutRowSpacing :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> m Word32
getGridLayoutRowSpacing o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"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 -> Word32 -> m ()
setGridLayoutRowSpacing :: forall (m :: * -> *) o.
(MonadIO m, IsGridLayout o) =>
o -> Word32 -> m ()
setGridLayoutRowSpacing o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"row-spacing" Word32
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, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructGridLayoutRowSpacing :: forall o (m :: * -> *).
(IsGridLayout o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructGridLayoutRowSpacing Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"row-spacing" Word32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutRowSpacingPropertyInfo
instance AttrInfo GridLayoutRowSpacingPropertyInfo where
    type AttrAllowedOps GridLayoutRowSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutRowSpacingPropertyInfo = IsGridLayout
    type AttrSetTypeConstraint GridLayoutRowSpacingPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint GridLayoutRowSpacingPropertyInfo = (~) Word32
    type AttrTransferType GridLayoutRowSpacingPropertyInfo = Word32
    type AttrGetType GridLayoutRowSpacingPropertyInfo = Word32
    type AttrLabel GridLayoutRowSpacingPropertyInfo = "row-spacing"
    type AttrOrigin GridLayoutRowSpacingPropertyInfo = GridLayout
    attrGet = getGridLayoutRowSpacing
    attrSet = setGridLayoutRowSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutRowSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.rowSpacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#g:attr:rowSpacing"
        })
#endif

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

#if defined(ENABLE_OVERLOADING)
gridLayoutColumnHomogeneous :: AttrLabelProxy "columnHomogeneous"
gridLayoutColumnHomogeneous = AttrLabelProxy

gridLayoutColumnSpacing :: AttrLabelProxy "columnSpacing"
gridLayoutColumnSpacing = AttrLabelProxy

gridLayoutOrientation :: AttrLabelProxy "orientation"
gridLayoutOrientation = AttrLabelProxy

gridLayoutRowHomogeneous :: AttrLabelProxy "rowHomogeneous"
gridLayoutRowHomogeneous = AttrLabelProxy

gridLayoutRowSpacing :: AttrLabelProxy "rowSpacing"
gridLayoutRowSpacing = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GridLayout = GridLayoutSignalList
type GridLayoutSignalList = ('[ '("layoutChanged", Clutter.LayoutManager.LayoutManagerLayoutChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

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

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

-- | Creates a new t'GI.Clutter.Objects.GridLayout.GridLayout'
gridLayoutNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m GridLayout
    -- ^ __Returns:__ the new t'GI.Clutter.Objects.GridLayout.GridLayout'
gridLayoutNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m GridLayout
gridLayoutNew  = IO GridLayout -> m GridLayout
forall a. IO a -> m a
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)
clutter_grid_layout_new
    Text -> Ptr GridLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"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
newObject ManagedPtr GridLayout -> GridLayout
GridLayout) Ptr GridLayout
result
    GridLayout -> IO GridLayout
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GridLayout
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method GridLayout::attach
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #ClutterActor to add"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "left"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the column number to attach the left side of @child to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "top"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the row number to attach the top side of @child to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of columns that @child will span"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of rows that @child will span"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_grid_layout_attach" clutter_grid_layout_attach :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    Ptr Clutter.Actor.Actor ->              -- child : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Int32 ->                                -- left : TBasicType TInt
    Int32 ->                                -- top : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Adds a widget to the grid.
-- 
-- The position of /@child@/ is determined by /@left@/ and /@top@/. The
-- number of \'cells\' that /@child@/ will occupy is determined by
-- /@width@/ and /@height@/.
-- 
-- /Since: 1.12/
gridLayoutAttach ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> b
    -- ^ /@child@/: the t'GI.Clutter.Objects.Actor.Actor' to add
    -> Int32
    -- ^ /@left@/: the column number to attach the left side of /@child@/ to
    -> Int32
    -- ^ /@top@/: the row number to attach the top side of /@child@/ to
    -> Int32
    -- ^ /@width@/: the number of columns that /@child@/ will span
    -> Int32
    -- ^ /@height@/: the number of rows that /@child@/ will span
    -> m ()
gridLayoutAttach :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsGridLayout a, IsActor b) =>
a -> b -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
gridLayoutAttach a
layout b
child Int32
left Int32
top Int32
width Int32
height = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
child' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr GridLayout
-> Ptr Actor -> Int32 -> Int32 -> Int32 -> Int32 -> IO ()
clutter_grid_layout_attach Ptr GridLayout
layout' Ptr Actor
child' Int32
left Int32
top Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutAttachMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsGridLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod GridLayoutAttachMethodInfo a signature where
    overloadedMethod = gridLayoutAttach

instance O.OverloadedMethodInfo GridLayoutAttachMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutAttach",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutAttach"
        })


#endif

-- method GridLayout::attach_next_to
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the actor to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sibling"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the child of @layout that @child will be placed\n    next to, or %NULL to place @child at the beginning or end"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "side"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridPosition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the side of @sibling that @child is positioned next to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of columns that @child will span"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of rows that @child will span"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_grid_layout_attach_next_to" clutter_grid_layout_attach_next_to :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    Ptr Clutter.Actor.Actor ->              -- child : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Ptr Clutter.Actor.Actor ->              -- sibling : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CUInt ->                                -- side : TInterface (Name {namespace = "Clutter", name = "GridPosition"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Adds a actor to the grid.
-- 
-- The actor is placed next to /@sibling@/, on the side determined by
-- /@side@/. When /@sibling@/ is 'P.Nothing', the actor is placed in row (for
-- left or right placement) or column 0 (for top or bottom placement),
-- at the end indicated by /@side@/.
-- 
-- Attaching widgets labeled [1], [2], [3] with /@sibling@/ == 'P.Nothing' and
-- /@side@/ == 'GI.Clutter.Enums.GridPositionLeft' yields a layout of [3][2][1].
-- 
-- /Since: 1.12/
gridLayoutAttachNextTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a, Clutter.Actor.IsActor b, Clutter.Actor.IsActor c) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> b
    -- ^ /@child@/: the actor to add
    -> Maybe (c)
    -- ^ /@sibling@/: the child of /@layout@/ that /@child@/ will be placed
    --     next to, or 'P.Nothing' to place /@child@/ at the beginning or end
    -> Clutter.Enums.GridPosition
    -- ^ /@side@/: the side of /@sibling@/ that /@child@/ is positioned next to
    -> Int32
    -- ^ /@width@/: the number of columns that /@child@/ will span
    -> Int32
    -- ^ /@height@/: the number of rows that /@child@/ will span
    -> m ()
gridLayoutAttachNextTo :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsGridLayout a, IsActor b, IsActor c) =>
a -> b -> Maybe c -> GridPosition -> Int32 -> Int32 -> m ()
gridLayoutAttachNextTo a
layout b
child Maybe c
sibling GridPosition
side Int32
width Int32
height = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
child' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr Actor
maybeSibling <- case Maybe c
sibling of
        Maybe c
Nothing -> Ptr Actor -> IO (Ptr Actor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Actor
forall a. Ptr a
nullPtr
        Just c
jSibling -> do
            Ptr Actor
jSibling' <- c -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jSibling
            Ptr Actor -> IO (Ptr Actor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Actor
jSibling'
    let side' :: CUInt
side' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (GridPosition -> Int) -> GridPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GridPosition -> Int
forall a. Enum a => a -> Int
fromEnum) GridPosition
side
    Ptr GridLayout
-> Ptr Actor -> Ptr Actor -> CUInt -> Int32 -> Int32 -> IO ()
clutter_grid_layout_attach_next_to Ptr GridLayout
layout' Ptr Actor
child' Ptr Actor
maybeSibling CUInt
side' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
sibling c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutAttachNextToMethodInfo
instance (signature ~ (b -> Maybe (c) -> Clutter.Enums.GridPosition -> Int32 -> Int32 -> m ()), MonadIO m, IsGridLayout a, Clutter.Actor.IsActor b, Clutter.Actor.IsActor c) => O.OverloadedMethod GridLayoutAttachNextToMethodInfo a signature where
    overloadedMethod = gridLayoutAttachNextTo

instance O.OverloadedMethodInfo GridLayoutAttachNextToMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutAttachNextTo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutAttachNextTo"
        })


#endif

-- method GridLayout::get_child_at
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "left"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the left edge of the cell"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "top"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the top edge of the cell"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Clutter" , name = "Actor" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_grid_layout_get_child_at" clutter_grid_layout_get_child_at :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    Int32 ->                                -- left : TBasicType TInt
    Int32 ->                                -- top : TBasicType TInt
    IO (Ptr Clutter.Actor.Actor)

-- | Gets the child of /@layout@/ whose area covers the grid
-- cell whose upper left corner is at /@left@/, /@top@/.
-- 
-- /Since: 1.12/
gridLayoutGetChildAt ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> Int32
    -- ^ /@left@/: the left edge of the cell
    -> Int32
    -- ^ /@top@/: the top edge of the cell
    -> m Clutter.Actor.Actor
    -- ^ __Returns:__ the child at the given position, or 'P.Nothing'
gridLayoutGetChildAt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> Int32 -> Int32 -> m Actor
gridLayoutGetChildAt a
layout Int32
left Int32
top = IO Actor -> m Actor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Actor -> m Actor) -> IO Actor -> m Actor
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
result <- Ptr GridLayout -> Int32 -> Int32 -> IO (Ptr Actor)
clutter_grid_layout_get_child_at Ptr GridLayout
layout' Int32
left Int32
top
    Text -> Ptr Actor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"gridLayoutGetChildAt" Ptr Actor
result
    Actor
result' <- ((ManagedPtr Actor -> Actor) -> Ptr Actor -> IO Actor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Actor -> Actor
Clutter.Actor.Actor) Ptr Actor
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Actor -> IO Actor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Actor
result'

#if defined(ENABLE_OVERLOADING)
data GridLayoutGetChildAtMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Clutter.Actor.Actor), MonadIO m, IsGridLayout a) => O.OverloadedMethod GridLayoutGetChildAtMethodInfo a signature where
    overloadedMethod = gridLayoutGetChildAt

instance O.OverloadedMethodInfo GridLayoutGetChildAtMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutGetChildAt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutGetChildAt"
        })


#endif

-- method GridLayout::get_column_homogeneous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , 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 "clutter_grid_layout_get_column_homogeneous" clutter_grid_layout_get_column_homogeneous :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    IO CInt

-- | Returns whether all columns of /@layout@/ have the same width.
gridLayoutGetColumnHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> m Bool
    -- ^ __Returns:__ whether all columns of /@layout@/ have the same width.
gridLayoutGetColumnHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> m Bool
gridLayoutGetColumnHomogeneous a
layout = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr GridLayout -> IO CInt
clutter_grid_layout_get_column_homogeneous Ptr GridLayout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bool -> IO Bool
forall a. a -> IO a
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.OverloadedMethod GridLayoutGetColumnHomogeneousMethodInfo a signature where
    overloadedMethod = gridLayoutGetColumnHomogeneous

instance O.OverloadedMethodInfo GridLayoutGetColumnHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutGetColumnHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutGetColumnHomogeneous"
        })


#endif

-- method GridLayout::get_column_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , 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 "clutter_grid_layout_get_column_spacing" clutter_grid_layout_get_column_spacing :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    IO Word32

-- | Retrieves the spacing set using 'GI.Clutter.Objects.GridLayout.gridLayoutSetColumnSpacing'
-- 
-- /Since: 1.12/
gridLayoutGetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> m Word32
    -- ^ __Returns:__ the spacing between coluns of /@layout@/
gridLayoutGetColumnSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> m Word32
gridLayoutGetColumnSpacing a
layout = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Word32
result <- Ptr GridLayout -> IO Word32
clutter_grid_layout_get_column_spacing Ptr GridLayout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Word32 -> IO Word32
forall a. a -> IO a
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.OverloadedMethod GridLayoutGetColumnSpacingMethodInfo a signature where
    overloadedMethod = gridLayoutGetColumnSpacing

instance O.OverloadedMethodInfo GridLayoutGetColumnSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutGetColumnSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutGetColumnSpacing"
        })


#endif

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

foreign import ccall "clutter_grid_layout_get_orientation" clutter_grid_layout_get_orientation :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    IO CUInt

-- | Retrieves the orientation of the /@layout@/.
-- 
-- /Since: 1.12/
gridLayoutGetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> m Clutter.Enums.Orientation
    -- ^ __Returns:__ the orientation of the layout
gridLayoutGetOrientation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> m Orientation
gridLayoutGetOrientation a
layout = IO Orientation -> m Orientation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Orientation -> m Orientation)
-> IO Orientation -> m Orientation
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CUInt
result <- Ptr GridLayout -> IO CUInt
clutter_grid_layout_get_orientation Ptr GridLayout
layout'
    let result' :: Orientation
result' = (Int -> Orientation
forall a. Enum a => Int -> a
toEnum (Int -> Orientation) -> (CUInt -> Int) -> CUInt -> Orientation
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
layout
    Orientation -> IO Orientation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
result'

#if defined(ENABLE_OVERLOADING)
data GridLayoutGetOrientationMethodInfo
instance (signature ~ (m Clutter.Enums.Orientation), MonadIO m, IsGridLayout a) => O.OverloadedMethod GridLayoutGetOrientationMethodInfo a signature where
    overloadedMethod = gridLayoutGetOrientation

instance O.OverloadedMethodInfo GridLayoutGetOrientationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutGetOrientation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutGetOrientation"
        })


#endif

-- method GridLayout::get_row_homogeneous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , 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 "clutter_grid_layout_get_row_homogeneous" clutter_grid_layout_get_row_homogeneous :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    IO CInt

-- | Returns whether all rows of /@layout@/ have the same height.
-- 
-- /Since: 1.12/
gridLayoutGetRowHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> m Bool
    -- ^ __Returns:__ whether all rows of /@layout@/ have the same height.
gridLayoutGetRowHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> m Bool
gridLayoutGetRowHomogeneous a
layout = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr GridLayout -> IO CInt
clutter_grid_layout_get_row_homogeneous Ptr GridLayout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bool -> IO Bool
forall a. a -> IO a
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.OverloadedMethod GridLayoutGetRowHomogeneousMethodInfo a signature where
    overloadedMethod = gridLayoutGetRowHomogeneous

instance O.OverloadedMethodInfo GridLayoutGetRowHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutGetRowHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutGetRowHomogeneous"
        })


#endif

-- method GridLayout::get_row_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , 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 "clutter_grid_layout_get_row_spacing" clutter_grid_layout_get_row_spacing :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    IO Word32

-- | Retrieves the spacing set using 'GI.Clutter.Objects.GridLayout.gridLayoutSetRowSpacing'
-- 
-- /Since: 1.12/
gridLayoutGetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> m Word32
    -- ^ __Returns:__ the spacing between rows of /@layout@/
gridLayoutGetRowSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> m Word32
gridLayoutGetRowSpacing a
layout = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Word32
result <- Ptr GridLayout -> IO Word32
clutter_grid_layout_get_row_spacing Ptr GridLayout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Word32 -> IO Word32
forall a. a -> IO a
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.OverloadedMethod GridLayoutGetRowSpacingMethodInfo a signature where
    overloadedMethod = gridLayoutGetRowSpacing

instance O.OverloadedMethodInfo GridLayoutGetRowSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutGetRowSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutGetRowSpacing"
        })


#endif

-- method GridLayout::insert_column
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position to insert the column at"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_grid_layout_insert_column" clutter_grid_layout_insert_column :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    Int32 ->                                -- position : TBasicType TInt
    IO ()

-- | Inserts a column at the specified position.
-- 
-- Children which are attached at or to the right of this position
-- are moved one column to the right. Children which span across this
-- position are grown to span the new column.
-- 
-- /Since: 1.12/
gridLayoutInsertColumn ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> Int32
    -- ^ /@position@/: the position to insert the column at
    -> m ()
gridLayoutInsertColumn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> Int32 -> m ()
gridLayoutInsertColumn a
layout Int32
position = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr GridLayout -> Int32 -> IO ()
clutter_grid_layout_insert_column Ptr GridLayout
layout' Int32
position
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutInsertColumnMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayout a) => O.OverloadedMethod GridLayoutInsertColumnMethodInfo a signature where
    overloadedMethod = gridLayoutInsertColumn

instance O.OverloadedMethodInfo GridLayoutInsertColumnMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutInsertColumn",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutInsertColumn"
        })


#endif

-- method GridLayout::insert_next_to
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sibling"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the child of @layout that the new row or column will be\n    placed next to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "side"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridPosition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the side of @sibling that @child is positioned next to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_grid_layout_insert_next_to" clutter_grid_layout_insert_next_to :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    Ptr Clutter.Actor.Actor ->              -- sibling : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CUInt ->                                -- side : TInterface (Name {namespace = "Clutter", name = "GridPosition"})
    IO ()

-- | Inserts a row or column at the specified position.
-- 
-- The new row or column is placed next to /@sibling@/, on the side
-- determined by /@side@/. If /@side@/ is 'GI.Clutter.Enums.GridPositionLeft' or
-- 'GI.Clutter.Enums.GridPositionBottom', a row is inserted. If /@side@/ is
-- 'GI.Clutter.Enums.GridPositionLeft' of 'GI.Clutter.Enums.GridPositionRight',
-- a column is inserted.
-- 
-- /Since: 1.12/
gridLayoutInsertNextTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> b
    -- ^ /@sibling@/: the child of /@layout@/ that the new row or column will be
    --     placed next to
    -> Clutter.Enums.GridPosition
    -- ^ /@side@/: the side of /@sibling@/ that /@child@/ is positioned next to
    -> m ()
gridLayoutInsertNextTo :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsGridLayout a, IsActor b) =>
a -> b -> GridPosition -> m ()
gridLayoutInsertNextTo a
layout b
sibling GridPosition
side = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
sibling' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
sibling
    let side' :: CUInt
side' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (GridPosition -> Int) -> GridPosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GridPosition -> Int
forall a. Enum a => a -> Int
fromEnum) GridPosition
side
    Ptr GridLayout -> Ptr Actor -> CUInt -> IO ()
clutter_grid_layout_insert_next_to Ptr GridLayout
layout' Ptr Actor
sibling' CUInt
side'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
sibling
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutInsertNextToMethodInfo
instance (signature ~ (b -> Clutter.Enums.GridPosition -> m ()), MonadIO m, IsGridLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod GridLayoutInsertNextToMethodInfo a signature where
    overloadedMethod = gridLayoutInsertNextTo

instance O.OverloadedMethodInfo GridLayoutInsertNextToMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutInsertNextTo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutInsertNextTo"
        })


#endif

-- method GridLayout::insert_row
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position to insert the row at"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_grid_layout_insert_row" clutter_grid_layout_insert_row :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    Int32 ->                                -- position : TBasicType TInt
    IO ()

-- | Inserts a row at the specified position.
-- 
-- Children which are attached at or below this position
-- are moved one row down. Children which span across this
-- position are grown to span the new row.
-- 
-- /Since: 1.12/
gridLayoutInsertRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> Int32
    -- ^ /@position@/: the position to insert the row at
    -> m ()
gridLayoutInsertRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> Int32 -> m ()
gridLayoutInsertRow a
layout Int32
position = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr GridLayout -> Int32 -> IO ()
clutter_grid_layout_insert_row Ptr GridLayout
layout' Int32
position
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutInsertRowMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayout a) => O.OverloadedMethod GridLayoutInsertRowMethodInfo a signature where
    overloadedMethod = gridLayoutInsertRow

instance O.OverloadedMethodInfo GridLayoutInsertRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutInsertRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutInsertRow"
        })


#endif

-- method GridLayout::set_column_homogeneous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , 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 "clutter_grid_layout_set_column_homogeneous" clutter_grid_layout_set_column_homogeneous :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    CInt ->                                 -- homogeneous : TBasicType TBoolean
    IO ()

-- | Sets whether all columns of /@layout@/ will have the same width.
-- 
-- /Since: 1.12/
gridLayoutSetColumnHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> Bool
    -- ^ /@homogeneous@/: 'P.True' to make columns homogeneous
    -> m ()
gridLayoutSetColumnHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> Bool -> m ()
gridLayoutSetColumnHomogeneous a
layout Bool
homogeneous = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let homogeneous' :: CInt
homogeneous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
homogeneous
    Ptr GridLayout -> CInt -> IO ()
clutter_grid_layout_set_column_homogeneous Ptr GridLayout
layout' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo GridLayoutSetColumnHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutSetColumnHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutSetColumnHomogeneous"
        })


#endif

-- method GridLayout::set_column_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , 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 spacing between columns of the layout, 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 "clutter_grid_layout_set_column_spacing" clutter_grid_layout_set_column_spacing :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    Word32 ->                               -- spacing : TBasicType TUInt
    IO ()

-- | Sets the spacing between columns of /@layout@/
-- 
-- /Since: 1.12/
gridLayoutSetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> Word32
    -- ^ /@spacing@/: the spacing between columns of the layout, in pixels
    -> m ()
gridLayoutSetColumnSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> Word32 -> m ()
gridLayoutSetColumnSpacing a
layout Word32
spacing = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr GridLayout -> Word32 -> IO ()
clutter_grid_layout_set_column_spacing Ptr GridLayout
layout' Word32
spacing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo GridLayoutSetColumnSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutSetColumnSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutSetColumnSpacing"
        })


#endif

-- method GridLayout::set_orientation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "orientation"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Orientation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the orientation of the #ClutterGridLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_grid_layout_set_orientation" clutter_grid_layout_set_orientation :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    CUInt ->                                -- orientation : TInterface (Name {namespace = "Clutter", name = "Orientation"})
    IO ()

-- | Sets the orientation of the /@layout@/.
-- 
-- t'GI.Clutter.Objects.GridLayout.GridLayout' uses the orientation as a hint when adding
-- children to the t'GI.Clutter.Objects.Actor.Actor' using it as a layout manager via
-- 'GI.Clutter.Objects.Actor.actorAddChild'; changing this value will not have
-- any effect on children that are already part of the layout.
-- 
-- /Since: 1.12/
gridLayoutSetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> Clutter.Enums.Orientation
    -- ^ /@orientation@/: the orientation of the t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> m ()
gridLayoutSetOrientation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> Orientation -> m ()
gridLayoutSetOrientation a
layout Orientation
orientation = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let orientation' :: CUInt
orientation' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Orientation -> Int) -> Orientation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Orientation -> Int
forall a. Enum a => a -> Int
fromEnum) Orientation
orientation
    Ptr GridLayout -> CUInt -> IO ()
clutter_grid_layout_set_orientation Ptr GridLayout
layout' CUInt
orientation'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutSetOrientationMethodInfo
instance (signature ~ (Clutter.Enums.Orientation -> m ()), MonadIO m, IsGridLayout a) => O.OverloadedMethod GridLayoutSetOrientationMethodInfo a signature where
    overloadedMethod = gridLayoutSetOrientation

instance O.OverloadedMethodInfo GridLayoutSetOrientationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutSetOrientation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutSetOrientation"
        })


#endif

-- method GridLayout::set_row_homogeneous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , 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 "clutter_grid_layout_set_row_homogeneous" clutter_grid_layout_set_row_homogeneous :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    CInt ->                                 -- homogeneous : TBasicType TBoolean
    IO ()

-- | Sets whether all rows of /@layout@/ will have the same height.
-- 
-- /Since: 1.12/
gridLayoutSetRowHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> Bool
    -- ^ /@homogeneous@/: 'P.True' to make rows homogeneous
    -> m ()
gridLayoutSetRowHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> Bool -> m ()
gridLayoutSetRowHomogeneous a
layout Bool
homogeneous = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let homogeneous' :: CInt
homogeneous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
homogeneous
    Ptr GridLayout -> CInt -> IO ()
clutter_grid_layout_set_row_homogeneous Ptr GridLayout
layout' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo GridLayoutSetRowHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutSetRowHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutSetRowHomogeneous"
        })


#endif

-- method GridLayout::set_row_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "GridLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterGridLayout"
--                 , 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 spacing between rows of the layout, 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 "clutter_grid_layout_set_row_spacing" clutter_grid_layout_set_row_spacing :: 
    Ptr GridLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "GridLayout"})
    Word32 ->                               -- spacing : TBasicType TUInt
    IO ()

-- | Sets the spacing between rows of /@layout@/
-- 
-- /Since: 1.12/
gridLayoutSetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.GridLayout.GridLayout'
    -> Word32
    -- ^ /@spacing@/: the spacing between rows of the layout, in pixels
    -> m ()
gridLayoutSetRowSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGridLayout a) =>
a -> Word32 -> m ()
gridLayoutSetRowSpacing a
layout Word32
spacing = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayout
layout' <- a -> IO (Ptr GridLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr GridLayout -> Word32 -> IO ()
clutter_grid_layout_set_row_spacing Ptr GridLayout
layout' Word32
spacing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo GridLayoutSetRowSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.GridLayout.gridLayoutSetRowSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-GridLayout.html#v:gridLayoutSetRowSpacing"
        })


#endif