{-# 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.TableLayout.TableLayout' structure contains only private data
-- and should be accessed using the provided API
-- 
-- /Since: 1.4/

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

module GI.Clutter.Objects.TableLayout
    ( 

-- * Exported types
    TableLayout(..)                         ,
    IsTableLayout                           ,
    toTableLayout                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [allocate]("GI.Clutter.Objects.LayoutManager#g:method:allocate"), [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"), [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"), [pack]("GI.Clutter.Objects.TableLayout#g:method:pack"), [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
-- [getAlignment]("GI.Clutter.Objects.TableLayout#g:method:getAlignment"), [getAnimationProgress]("GI.Clutter.Objects.LayoutManager#g:method:getAnimationProgress"), [getChildMeta]("GI.Clutter.Objects.LayoutManager#g:method:getChildMeta"), [getColumnCount]("GI.Clutter.Objects.TableLayout#g:method:getColumnCount"), [getColumnSpacing]("GI.Clutter.Objects.TableLayout#g:method:getColumnSpacing"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getEasingDuration]("GI.Clutter.Objects.TableLayout#g:method:getEasingDuration"), [getEasingMode]("GI.Clutter.Objects.TableLayout#g:method:getEasingMode"), [getExpand]("GI.Clutter.Objects.TableLayout#g:method:getExpand"), [getFill]("GI.Clutter.Objects.TableLayout#g:method:getFill"), [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"), [getRowCount]("GI.Clutter.Objects.TableLayout#g:method:getRowCount"), [getRowSpacing]("GI.Clutter.Objects.TableLayout#g:method:getRowSpacing"), [getSpan]("GI.Clutter.Objects.TableLayout#g:method:getSpan"), [getUseAnimations]("GI.Clutter.Objects.TableLayout#g:method:getUseAnimations").
-- 
-- ==== Setters
-- [setAlignment]("GI.Clutter.Objects.TableLayout#g:method:setAlignment"), [setColumnSpacing]("GI.Clutter.Objects.TableLayout#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"), [setEasingDuration]("GI.Clutter.Objects.TableLayout#g:method:setEasingDuration"), [setEasingMode]("GI.Clutter.Objects.TableLayout#g:method:setEasingMode"), [setExpand]("GI.Clutter.Objects.TableLayout#g:method:setExpand"), [setFill]("GI.Clutter.Objects.TableLayout#g:method:setFill"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRowSpacing]("GI.Clutter.Objects.TableLayout#g:method:setRowSpacing"), [setSpan]("GI.Clutter.Objects.TableLayout#g:method:setSpan"), [setUseAnimations]("GI.Clutter.Objects.TableLayout#g:method:setUseAnimations").

#if defined(ENABLE_OVERLOADING)
    ResolveTableLayoutMethod                ,
#endif

-- ** getAlignment #method:getAlignment#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetAlignmentMethodInfo       ,
#endif
    tableLayoutGetAlignment                 ,


-- ** getColumnCount #method:getColumnCount#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetColumnCountMethodInfo     ,
#endif
    tableLayoutGetColumnCount               ,


-- ** getColumnSpacing #method:getColumnSpacing#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetColumnSpacingMethodInfo   ,
#endif
    tableLayoutGetColumnSpacing             ,


-- ** getEasingDuration #method:getEasingDuration#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetEasingDurationMethodInfo  ,
#endif
    tableLayoutGetEasingDuration            ,


-- ** getEasingMode #method:getEasingMode#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetEasingModeMethodInfo      ,
#endif
    tableLayoutGetEasingMode                ,


-- ** getExpand #method:getExpand#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetExpandMethodInfo          ,
#endif
    tableLayoutGetExpand                    ,


-- ** getFill #method:getFill#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetFillMethodInfo            ,
#endif
    tableLayoutGetFill                      ,


-- ** getRowCount #method:getRowCount#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetRowCountMethodInfo        ,
#endif
    tableLayoutGetRowCount                  ,


-- ** getRowSpacing #method:getRowSpacing#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetRowSpacingMethodInfo      ,
#endif
    tableLayoutGetRowSpacing                ,


-- ** getSpan #method:getSpan#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetSpanMethodInfo            ,
#endif
    tableLayoutGetSpan                      ,


-- ** getUseAnimations #method:getUseAnimations#

#if defined(ENABLE_OVERLOADING)
    TableLayoutGetUseAnimationsMethodInfo   ,
#endif
    tableLayoutGetUseAnimations             ,


-- ** new #method:new#

    tableLayoutNew                          ,


-- ** pack #method:pack#

#if defined(ENABLE_OVERLOADING)
    TableLayoutPackMethodInfo               ,
#endif
    tableLayoutPack                         ,


-- ** setAlignment #method:setAlignment#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetAlignmentMethodInfo       ,
#endif
    tableLayoutSetAlignment                 ,


-- ** setColumnSpacing #method:setColumnSpacing#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetColumnSpacingMethodInfo   ,
#endif
    tableLayoutSetColumnSpacing             ,


-- ** setEasingDuration #method:setEasingDuration#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetEasingDurationMethodInfo  ,
#endif
    tableLayoutSetEasingDuration            ,


-- ** setEasingMode #method:setEasingMode#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetEasingModeMethodInfo      ,
#endif
    tableLayoutSetEasingMode                ,


-- ** setExpand #method:setExpand#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetExpandMethodInfo          ,
#endif
    tableLayoutSetExpand                    ,


-- ** setFill #method:setFill#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetFillMethodInfo            ,
#endif
    tableLayoutSetFill                      ,


-- ** setRowSpacing #method:setRowSpacing#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetRowSpacingMethodInfo      ,
#endif
    tableLayoutSetRowSpacing                ,


-- ** setSpan #method:setSpan#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetSpanMethodInfo            ,
#endif
    tableLayoutSetSpan                      ,


-- ** setUseAnimations #method:setUseAnimations#

#if defined(ENABLE_OVERLOADING)
    TableLayoutSetUseAnimationsMethodInfo   ,
#endif
    tableLayoutSetUseAnimations             ,




 -- * Properties


-- ** columnSpacing #attr:columnSpacing#
-- | The spacing between columns of the t'GI.Clutter.Objects.TableLayout.TableLayout', in pixels
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    TableLayoutColumnSpacingPropertyInfo    ,
#endif
    constructTableLayoutColumnSpacing       ,
    getTableLayoutColumnSpacing             ,
    setTableLayoutColumnSpacing             ,
#if defined(ENABLE_OVERLOADING)
    tableLayoutColumnSpacing                ,
#endif


-- ** easingDuration #attr:easingDuration#
-- | The duration of the animations, in case [TableLayout:useAnimations]("GI.Clutter.Objects.TableLayout#g:attr:useAnimations")
-- is set to 'P.True'.
-- 
-- The duration is expressed in milliseconds.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    TableLayoutEasingDurationPropertyInfo   ,
#endif
    constructTableLayoutEasingDuration      ,
    getTableLayoutEasingDuration            ,
    setTableLayoutEasingDuration            ,
#if defined(ENABLE_OVERLOADING)
    tableLayoutEasingDuration               ,
#endif


-- ** easingMode #attr:easingMode#
-- | The easing mode for the animations, in case
-- [TableLayout:useAnimations]("GI.Clutter.Objects.TableLayout#g:attr:useAnimations") is set to 'P.True'.
-- 
-- The easing mode has the same semantics of [Animation:mode]("GI.Clutter.Objects.Animation#g:attr:mode"): it can
-- either be a value from the t'GI.Clutter.Enums.AnimationMode' enumeration, like
-- 'GI.Clutter.Enums.AnimationModeEaseOutCubic', or a logical id as returned by
-- @/clutter_alpha_register_func()/@.
-- 
-- The default value is 'GI.Clutter.Enums.AnimationModeEaseOutCubic'.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    TableLayoutEasingModePropertyInfo       ,
#endif
    constructTableLayoutEasingMode          ,
    getTableLayoutEasingMode                ,
    setTableLayoutEasingMode                ,
#if defined(ENABLE_OVERLOADING)
    tableLayoutEasingMode                   ,
#endif


-- ** rowSpacing #attr:rowSpacing#
-- | The spacing between rows of the t'GI.Clutter.Objects.TableLayout.TableLayout', in pixels
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    TableLayoutRowSpacingPropertyInfo       ,
#endif
    constructTableLayoutRowSpacing          ,
    getTableLayoutRowSpacing                ,
    setTableLayoutRowSpacing                ,
#if defined(ENABLE_OVERLOADING)
    tableLayoutRowSpacing                   ,
#endif


-- ** useAnimations #attr:useAnimations#
-- | Whether the t'GI.Clutter.Objects.TableLayout.TableLayout' should animate changes in the
-- layout properties.
-- 
-- By default, t'GI.Clutter.Objects.TableLayout.TableLayout' will honour the easing state of
-- the children when allocating them. Setting this property to
-- 'P.True' will override the easing state with the layout manager\'s
-- [TableLayout:easingMode]("GI.Clutter.Objects.TableLayout#g:attr:easingMode") and [TableLayout:easingDuration]("GI.Clutter.Objects.TableLayout#g:attr:easingDuration")
-- properties.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    TableLayoutUseAnimationsPropertyInfo    ,
#endif
    constructTableLayoutUseAnimations       ,
    getTableLayoutUseAnimations             ,
    setTableLayoutUseAnimations             ,
#if defined(ENABLE_OVERLOADING)
    tableLayoutUseAnimations                ,
#endif




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.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 TableLayout = TableLayout (SP.ManagedPtr TableLayout)
    deriving (TableLayout -> TableLayout -> Bool
(TableLayout -> TableLayout -> Bool)
-> (TableLayout -> TableLayout -> Bool) -> Eq TableLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TableLayout -> TableLayout -> Bool
== :: TableLayout -> TableLayout -> Bool
$c/= :: TableLayout -> TableLayout -> Bool
/= :: TableLayout -> TableLayout -> Bool
Eq)

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

foreign import ccall "clutter_table_layout_get_type"
    c_clutter_table_layout_get_type :: IO B.Types.GType

instance B.Types.TypedObject TableLayout where
    glibType :: IO GType
glibType = IO GType
c_clutter_table_layout_get_type

instance B.Types.GObject TableLayout

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

instance O.HasParentTypes TableLayout
type instance O.ParentTypes TableLayout = '[Clutter.LayoutManager.LayoutManager, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveTableLayoutMethod (t :: Symbol) (o :: *) :: * where
    ResolveTableLayoutMethod "allocate" o = Clutter.LayoutManager.LayoutManagerAllocateMethodInfo
    ResolveTableLayoutMethod "beginAnimation" o = Clutter.LayoutManager.LayoutManagerBeginAnimationMethodInfo
    ResolveTableLayoutMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTableLayoutMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTableLayoutMethod "childGetProperty" o = Clutter.LayoutManager.LayoutManagerChildGetPropertyMethodInfo
    ResolveTableLayoutMethod "childSetProperty" o = Clutter.LayoutManager.LayoutManagerChildSetPropertyMethodInfo
    ResolveTableLayoutMethod "endAnimation" o = Clutter.LayoutManager.LayoutManagerEndAnimationMethodInfo
    ResolveTableLayoutMethod "findChildProperty" o = Clutter.LayoutManager.LayoutManagerFindChildPropertyMethodInfo
    ResolveTableLayoutMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTableLayoutMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTableLayoutMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTableLayoutMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTableLayoutMethod "layoutChanged" o = Clutter.LayoutManager.LayoutManagerLayoutChangedMethodInfo
    ResolveTableLayoutMethod "listChildProperties" o = Clutter.LayoutManager.LayoutManagerListChildPropertiesMethodInfo
    ResolveTableLayoutMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTableLayoutMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTableLayoutMethod "pack" o = TableLayoutPackMethodInfo
    ResolveTableLayoutMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTableLayoutMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTableLayoutMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTableLayoutMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTableLayoutMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTableLayoutMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTableLayoutMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTableLayoutMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTableLayoutMethod "getAlignment" o = TableLayoutGetAlignmentMethodInfo
    ResolveTableLayoutMethod "getAnimationProgress" o = Clutter.LayoutManager.LayoutManagerGetAnimationProgressMethodInfo
    ResolveTableLayoutMethod "getChildMeta" o = Clutter.LayoutManager.LayoutManagerGetChildMetaMethodInfo
    ResolveTableLayoutMethod "getColumnCount" o = TableLayoutGetColumnCountMethodInfo
    ResolveTableLayoutMethod "getColumnSpacing" o = TableLayoutGetColumnSpacingMethodInfo
    ResolveTableLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTableLayoutMethod "getEasingDuration" o = TableLayoutGetEasingDurationMethodInfo
    ResolveTableLayoutMethod "getEasingMode" o = TableLayoutGetEasingModeMethodInfo
    ResolveTableLayoutMethod "getExpand" o = TableLayoutGetExpandMethodInfo
    ResolveTableLayoutMethod "getFill" o = TableLayoutGetFillMethodInfo
    ResolveTableLayoutMethod "getPreferredHeight" o = Clutter.LayoutManager.LayoutManagerGetPreferredHeightMethodInfo
    ResolveTableLayoutMethod "getPreferredWidth" o = Clutter.LayoutManager.LayoutManagerGetPreferredWidthMethodInfo
    ResolveTableLayoutMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTableLayoutMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTableLayoutMethod "getRowCount" o = TableLayoutGetRowCountMethodInfo
    ResolveTableLayoutMethod "getRowSpacing" o = TableLayoutGetRowSpacingMethodInfo
    ResolveTableLayoutMethod "getSpan" o = TableLayoutGetSpanMethodInfo
    ResolveTableLayoutMethod "getUseAnimations" o = TableLayoutGetUseAnimationsMethodInfo
    ResolveTableLayoutMethod "setAlignment" o = TableLayoutSetAlignmentMethodInfo
    ResolveTableLayoutMethod "setColumnSpacing" o = TableLayoutSetColumnSpacingMethodInfo
    ResolveTableLayoutMethod "setContainer" o = Clutter.LayoutManager.LayoutManagerSetContainerMethodInfo
    ResolveTableLayoutMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTableLayoutMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTableLayoutMethod "setEasingDuration" o = TableLayoutSetEasingDurationMethodInfo
    ResolveTableLayoutMethod "setEasingMode" o = TableLayoutSetEasingModeMethodInfo
    ResolveTableLayoutMethod "setExpand" o = TableLayoutSetExpandMethodInfo
    ResolveTableLayoutMethod "setFill" o = TableLayoutSetFillMethodInfo
    ResolveTableLayoutMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTableLayoutMethod "setRowSpacing" o = TableLayoutSetRowSpacingMethodInfo
    ResolveTableLayoutMethod "setSpan" o = TableLayoutSetSpanMethodInfo
    ResolveTableLayoutMethod "setUseAnimations" o = TableLayoutSetUseAnimationsMethodInfo
    ResolveTableLayoutMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#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' tableLayout #columnSpacing
-- @
getTableLayoutColumnSpacing :: (MonadIO m, IsTableLayout o) => o -> m Word32
getTableLayoutColumnSpacing :: forall (m :: * -> *) o.
(MonadIO m, IsTableLayout o) =>
o -> m Word32
getTableLayoutColumnSpacing 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' tableLayout [ #columnSpacing 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableLayoutColumnSpacing :: (MonadIO m, IsTableLayout o) => o -> Word32 -> m ()
setTableLayoutColumnSpacing :: forall (m :: * -> *) o.
(MonadIO m, IsTableLayout o) =>
o -> Word32 -> m ()
setTableLayoutColumnSpacing 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`.
constructTableLayoutColumnSpacing :: (IsTableLayout o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructTableLayoutColumnSpacing :: forall o (m :: * -> *).
(IsTableLayout o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructTableLayoutColumnSpacing 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 TableLayoutColumnSpacingPropertyInfo
instance AttrInfo TableLayoutColumnSpacingPropertyInfo where
    type AttrAllowedOps TableLayoutColumnSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TableLayoutColumnSpacingPropertyInfo = IsTableLayout
    type AttrSetTypeConstraint TableLayoutColumnSpacingPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint TableLayoutColumnSpacingPropertyInfo = (~) Word32
    type AttrTransferType TableLayoutColumnSpacingPropertyInfo = Word32
    type AttrGetType TableLayoutColumnSpacingPropertyInfo = Word32
    type AttrLabel TableLayoutColumnSpacingPropertyInfo = "column-spacing"
    type AttrOrigin TableLayoutColumnSpacingPropertyInfo = TableLayout
    attrGet = getTableLayoutColumnSpacing
    attrSet = setTableLayoutColumnSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructTableLayoutColumnSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.TableLayout.columnSpacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-TableLayout.html#g:attr:columnSpacing"
        })
#endif

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

-- | Get the value of the “@easing-duration@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableLayout #easingDuration
-- @
getTableLayoutEasingDuration :: (MonadIO m, IsTableLayout o) => o -> m Word32
getTableLayoutEasingDuration :: forall (m :: * -> *) o.
(MonadIO m, IsTableLayout o) =>
o -> m Word32
getTableLayoutEasingDuration 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
"easing-duration"

-- | Set the value of the “@easing-duration@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableLayout [ #easingDuration 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableLayoutEasingDuration :: (MonadIO m, IsTableLayout o) => o -> Word32 -> m ()
setTableLayoutEasingDuration :: forall (m :: * -> *) o.
(MonadIO m, IsTableLayout o) =>
o -> Word32 -> m ()
setTableLayoutEasingDuration 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
"easing-duration" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@easing-duration@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTableLayoutEasingDuration :: (IsTableLayout o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructTableLayoutEasingDuration :: forall o (m :: * -> *).
(IsTableLayout o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructTableLayoutEasingDuration 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
"easing-duration" Word32
val

#if defined(ENABLE_OVERLOADING)
data TableLayoutEasingDurationPropertyInfo
instance AttrInfo TableLayoutEasingDurationPropertyInfo where
    type AttrAllowedOps TableLayoutEasingDurationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TableLayoutEasingDurationPropertyInfo = IsTableLayout
    type AttrSetTypeConstraint TableLayoutEasingDurationPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint TableLayoutEasingDurationPropertyInfo = (~) Word32
    type AttrTransferType TableLayoutEasingDurationPropertyInfo = Word32
    type AttrGetType TableLayoutEasingDurationPropertyInfo = Word32
    type AttrLabel TableLayoutEasingDurationPropertyInfo = "easing-duration"
    type AttrOrigin TableLayoutEasingDurationPropertyInfo = TableLayout
    attrGet = getTableLayoutEasingDuration
    attrSet = setTableLayoutEasingDuration
    attrTransfer _ v = do
        return v
    attrConstruct = constructTableLayoutEasingDuration
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.TableLayout.easingDuration"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-TableLayout.html#g:attr:easingDuration"
        })
#endif

-- VVV Prop "easing-mode"
   -- Type: TBasicType TULong
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

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

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

#if defined(ENABLE_OVERLOADING)
data TableLayoutEasingModePropertyInfo
instance AttrInfo TableLayoutEasingModePropertyInfo where
    type AttrAllowedOps TableLayoutEasingModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TableLayoutEasingModePropertyInfo = IsTableLayout
    type AttrSetTypeConstraint TableLayoutEasingModePropertyInfo = (~) CULong
    type AttrTransferTypeConstraint TableLayoutEasingModePropertyInfo = (~) CULong
    type AttrTransferType TableLayoutEasingModePropertyInfo = CULong
    type AttrGetType TableLayoutEasingModePropertyInfo = CULong
    type AttrLabel TableLayoutEasingModePropertyInfo = "easing-mode"
    type AttrOrigin TableLayoutEasingModePropertyInfo = TableLayout
    attrGet = getTableLayoutEasingMode
    attrSet = setTableLayoutEasingMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructTableLayoutEasingMode
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.TableLayout.easingMode"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-TableLayout.html#g:attr:easingMode"
        })
#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' tableLayout #rowSpacing
-- @
getTableLayoutRowSpacing :: (MonadIO m, IsTableLayout o) => o -> m Word32
getTableLayoutRowSpacing :: forall (m :: * -> *) o.
(MonadIO m, IsTableLayout o) =>
o -> m Word32
getTableLayoutRowSpacing 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' tableLayout [ #rowSpacing 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableLayoutRowSpacing :: (MonadIO m, IsTableLayout o) => o -> Word32 -> m ()
setTableLayoutRowSpacing :: forall (m :: * -> *) o.
(MonadIO m, IsTableLayout o) =>
o -> Word32 -> m ()
setTableLayoutRowSpacing 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`.
constructTableLayoutRowSpacing :: (IsTableLayout o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructTableLayoutRowSpacing :: forall o (m :: * -> *).
(IsTableLayout o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructTableLayoutRowSpacing 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 TableLayoutRowSpacingPropertyInfo
instance AttrInfo TableLayoutRowSpacingPropertyInfo where
    type AttrAllowedOps TableLayoutRowSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TableLayoutRowSpacingPropertyInfo = IsTableLayout
    type AttrSetTypeConstraint TableLayoutRowSpacingPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint TableLayoutRowSpacingPropertyInfo = (~) Word32
    type AttrTransferType TableLayoutRowSpacingPropertyInfo = Word32
    type AttrGetType TableLayoutRowSpacingPropertyInfo = Word32
    type AttrLabel TableLayoutRowSpacingPropertyInfo = "row-spacing"
    type AttrOrigin TableLayoutRowSpacingPropertyInfo = TableLayout
    attrGet = getTableLayoutRowSpacing
    attrSet = setTableLayoutRowSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructTableLayoutRowSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.TableLayout.rowSpacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-TableLayout.html#g:attr:rowSpacing"
        })
#endif

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

-- | Get the value of the “@use-animations@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableLayout #useAnimations
-- @
getTableLayoutUseAnimations :: (MonadIO m, IsTableLayout o) => o -> m Bool
getTableLayoutUseAnimations :: forall (m :: * -> *) o. (MonadIO m, IsTableLayout o) => o -> m Bool
getTableLayoutUseAnimations 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
"use-animations"

-- | Set the value of the “@use-animations@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableLayout [ #useAnimations 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableLayoutUseAnimations :: (MonadIO m, IsTableLayout o) => o -> Bool -> m ()
setTableLayoutUseAnimations :: forall (m :: * -> *) o.
(MonadIO m, IsTableLayout o) =>
o -> Bool -> m ()
setTableLayoutUseAnimations 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
"use-animations" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@use-animations@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructTableLayoutUseAnimations :: (IsTableLayout o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTableLayoutUseAnimations :: forall o (m :: * -> *).
(IsTableLayout o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTableLayoutUseAnimations 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
"use-animations" Bool
val

#if defined(ENABLE_OVERLOADING)
data TableLayoutUseAnimationsPropertyInfo
instance AttrInfo TableLayoutUseAnimationsPropertyInfo where
    type AttrAllowedOps TableLayoutUseAnimationsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint TableLayoutUseAnimationsPropertyInfo = IsTableLayout
    type AttrSetTypeConstraint TableLayoutUseAnimationsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint TableLayoutUseAnimationsPropertyInfo = (~) Bool
    type AttrTransferType TableLayoutUseAnimationsPropertyInfo = Bool
    type AttrGetType TableLayoutUseAnimationsPropertyInfo = Bool
    type AttrLabel TableLayoutUseAnimationsPropertyInfo = "use-animations"
    type AttrOrigin TableLayoutUseAnimationsPropertyInfo = TableLayout
    attrGet = getTableLayoutUseAnimations
    attrSet = setTableLayoutUseAnimations
    attrTransfer _ v = do
        return v
    attrConstruct = constructTableLayoutUseAnimations
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.TableLayout.useAnimations"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-TableLayout.html#g:attr:useAnimations"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TableLayout
type instance O.AttributeList TableLayout = TableLayoutAttributeList
type TableLayoutAttributeList = ('[ '("columnSpacing", TableLayoutColumnSpacingPropertyInfo), '("easingDuration", TableLayoutEasingDurationPropertyInfo), '("easingMode", TableLayoutEasingModePropertyInfo), '("rowSpacing", TableLayoutRowSpacingPropertyInfo), '("useAnimations", TableLayoutUseAnimationsPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
tableLayoutColumnSpacing :: AttrLabelProxy "columnSpacing"
tableLayoutColumnSpacing = AttrLabelProxy

tableLayoutEasingDuration :: AttrLabelProxy "easingDuration"
tableLayoutEasingDuration = AttrLabelProxy

tableLayoutEasingMode :: AttrLabelProxy "easingMode"
tableLayoutEasingMode = AttrLabelProxy

tableLayoutRowSpacing :: AttrLabelProxy "rowSpacing"
tableLayoutRowSpacing = AttrLabelProxy

tableLayoutUseAnimations :: AttrLabelProxy "useAnimations"
tableLayoutUseAnimations = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TableLayout = TableLayoutSignalList
type TableLayoutSignalList = ('[ '("layoutChanged", Clutter.LayoutManager.LayoutManagerLayoutChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "clutter_table_layout_new" clutter_table_layout_new :: 
    IO (Ptr TableLayout)

{-# DEPRECATED tableLayoutNew ["(Since version 1.18)","Use t'GI.Clutter.Objects.GridLayout.GridLayout' instead"] #-}
-- | Creates a new t'GI.Clutter.Objects.TableLayout.TableLayout' layout manager
-- 
-- /Since: 1.4/
tableLayoutNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m TableLayout
    -- ^ __Returns:__ the newly created t'GI.Clutter.Objects.TableLayout.TableLayout'
tableLayoutNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m TableLayout
tableLayoutNew  = IO TableLayout -> m TableLayout
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TableLayout -> m TableLayout)
-> IO TableLayout -> m TableLayout
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableLayout
result <- IO (Ptr TableLayout)
clutter_table_layout_new
    Text -> Ptr TableLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tableLayoutNew" Ptr TableLayout
result
    TableLayout
result' <- ((ManagedPtr TableLayout -> TableLayout)
-> Ptr TableLayout -> IO TableLayout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TableLayout -> TableLayout
TableLayout) Ptr TableLayout
result
    TableLayout -> IO TableLayout
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TableLayout
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method TableLayout::get_alignment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor child of @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_align"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableAlignment" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the horizontal alignment policy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y_align"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableAlignment" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the vertical alignment policy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_get_alignment" clutter_table_layout_get_alignment :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Ptr CUInt ->                            -- x_align : TInterface (Name {namespace = "Clutter", name = "TableAlignment"})
    Ptr CUInt ->                            -- y_align : TInterface (Name {namespace = "Clutter", name = "TableAlignment"})
    IO ()

{-# DEPRECATED tableLayoutGetAlignment ["(Since version 1.12)","Use 'GI.Clutter.Objects.Actor.actorGetXAlign' and","  'GI.Clutter.Objects.Actor.actorGetYAlign' instead."] #-}
-- | Retrieves the horizontal and vertical alignment policies for /@actor@/
-- as set using 'GI.Clutter.Objects.TableLayout.tableLayoutPack' or
-- 'GI.Clutter.Objects.TableLayout.tableLayoutSetAlignment'.
-- 
-- /Since: 1.4/
tableLayoutGetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> m ((Clutter.Enums.TableAlignment, Clutter.Enums.TableAlignment))
tableLayoutGetAlignment :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> m (TableAlignment, TableAlignment)
tableLayoutGetAlignment a
layout b
actor = IO (TableAlignment, TableAlignment)
-> m (TableAlignment, TableAlignment)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (TableAlignment, TableAlignment)
 -> m (TableAlignment, TableAlignment))
-> IO (TableAlignment, TableAlignment)
-> m (TableAlignment, TableAlignment)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    Ptr CUInt
xAlign <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    Ptr CUInt
yAlign <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    Ptr TableLayout -> Ptr Actor -> Ptr CUInt -> Ptr CUInt -> IO ()
clutter_table_layout_get_alignment Ptr TableLayout
layout' Ptr Actor
actor' Ptr CUInt
xAlign Ptr CUInt
yAlign
    CUInt
xAlign' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
xAlign
    let xAlign'' :: TableAlignment
xAlign'' = (Int -> TableAlignment
forall a. Enum a => Int -> a
toEnum (Int -> TableAlignment)
-> (CUInt -> Int) -> CUInt -> TableAlignment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
xAlign'
    CUInt
yAlign' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
yAlign
    let yAlign'' :: TableAlignment
yAlign'' = (Int -> TableAlignment
forall a. Enum a => Int -> a
toEnum (Int -> TableAlignment)
-> (CUInt -> Int) -> CUInt -> TableAlignment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
yAlign'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
xAlign
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
yAlign
    (TableAlignment, TableAlignment)
-> IO (TableAlignment, TableAlignment)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TableAlignment
xAlign'', TableAlignment
yAlign'')

#if defined(ENABLE_OVERLOADING)
data TableLayoutGetAlignmentMethodInfo
instance (signature ~ (b -> m ((Clutter.Enums.TableAlignment, Clutter.Enums.TableAlignment))), MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod TableLayoutGetAlignmentMethodInfo a signature where
    overloadedMethod = tableLayoutGetAlignment

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


#endif

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

foreign import ccall "clutter_table_layout_get_column_count" clutter_table_layout_get_column_count :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    IO Int32

{-# DEPRECATED tableLayoutGetColumnCount ["(Since version 1.18)","No direct replacement is available"] #-}
-- | Retrieve the current number of columns in /@layout@/
-- 
-- /Since: 1.4/
tableLayoutGetColumnCount ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: A t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> m Int32
    -- ^ __Returns:__ the number of columns
tableLayoutGetColumnCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> m Int32
tableLayoutGetColumnCount a
layout = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr TableLayout -> IO Int32
clutter_table_layout_get_column_count Ptr TableLayout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TableLayoutGetColumnCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutGetColumnCountMethodInfo a signature where
    overloadedMethod = tableLayoutGetColumnCount

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


#endif

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

{-# DEPRECATED tableLayoutGetColumnSpacing ["(Since version 1.18)","Use [GridLayout:columnSpacing](\"GI.Clutter.Objects.GridLayout#g:attr:columnSpacing\")"] #-}
-- | Retrieves the spacing set using 'GI.Clutter.Objects.TableLayout.tableLayoutSetColumnSpacing'
-- 
-- /Since: 1.4/
tableLayoutGetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> m Word32
    -- ^ __Returns:__ the spacing between columns of the t'GI.Clutter.Objects.TableLayout.TableLayout'
tableLayoutGetColumnSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> m Word32
tableLayoutGetColumnSpacing 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Word32
result <- Ptr TableLayout -> IO Word32
clutter_table_layout_get_column_spacing Ptr TableLayout
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 TableLayoutGetColumnSpacingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutGetColumnSpacingMethodInfo a signature where
    overloadedMethod = tableLayoutGetColumnSpacing

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


#endif

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

{-# DEPRECATED tableLayoutGetEasingDuration ["(Since version 1.12)","t'GI.Clutter.Objects.TableLayout.TableLayout' will honour the easing state","  of the children when allocating them. See 'GI.Clutter.Objects.Actor.actorSetEasingMode'","  and 'GI.Clutter.Objects.Actor.actorSetEasingDuration'."] #-}
-- | Retrieves the duration set using 'GI.Clutter.Objects.TableLayout.tableLayoutSetEasingDuration'
-- 
-- /Since: 1.4/
tableLayoutGetEasingDuration ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> m Word32
    -- ^ __Returns:__ the duration of the animations, in milliseconds
tableLayoutGetEasingDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> m Word32
tableLayoutGetEasingDuration 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Word32
result <- Ptr TableLayout -> IO Word32
clutter_table_layout_get_easing_duration Ptr TableLayout
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 TableLayoutGetEasingDurationMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutGetEasingDurationMethodInfo a signature where
    overloadedMethod = tableLayoutGetEasingDuration

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


#endif

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

foreign import ccall "clutter_table_layout_get_easing_mode" clutter_table_layout_get_easing_mode :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    IO CULong

{-# DEPRECATED tableLayoutGetEasingMode ["(Since version 1.12)","t'GI.Clutter.Objects.TableLayout.TableLayout' will honour the easing state","  of the children when allocating them. See 'GI.Clutter.Objects.Actor.actorSetEasingMode'","  and 'GI.Clutter.Objects.Actor.actorSetEasingDuration'."] #-}
-- | Retrieves the easing mode set using 'GI.Clutter.Objects.TableLayout.tableLayoutSetEasingMode'
-- 
-- /Since: 1.4/
tableLayoutGetEasingMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> m CULong
    -- ^ __Returns:__ an easing mode
tableLayoutGetEasingMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> m CULong
tableLayoutGetEasingMode a
layout = IO CULong -> m CULong
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CULong -> m CULong) -> IO CULong -> m CULong
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CULong
result <- Ptr TableLayout -> IO CULong
clutter_table_layout_get_easing_mode Ptr TableLayout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    CULong -> IO CULong
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CULong
result

#if defined(ENABLE_OVERLOADING)
data TableLayoutGetEasingModeMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutGetEasingModeMethodInfo a signature where
    overloadedMethod = tableLayoutGetEasingMode

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


#endif

-- method TableLayout::get_expand
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor child of @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_expand"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the horizontal expand policy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y_expand"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the vertical expand policy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_get_expand" clutter_table_layout_get_expand :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Ptr CInt ->                             -- x_expand : TBasicType TBoolean
    Ptr CInt ->                             -- y_expand : TBasicType TBoolean
    IO ()

{-# DEPRECATED tableLayoutGetExpand ["(Since version 1.12)","Use 'GI.Clutter.Objects.Actor.actorGetXExpand' and","  'GI.Clutter.Objects.Actor.actorGetYExpand' instead."] #-}
-- | Retrieves the horizontal and vertical expand policies for /@actor@/
-- as set using 'GI.Clutter.Objects.TableLayout.tableLayoutPack' or 'GI.Clutter.Objects.TableLayout.tableLayoutSetExpand'
-- 
-- /Since: 1.4/
tableLayoutGetExpand ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> m ((Bool, Bool))
tableLayoutGetExpand :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> m (Bool, Bool)
tableLayoutGetExpand a
layout b
actor = IO (Bool, Bool) -> m (Bool, Bool)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Bool) -> m (Bool, Bool))
-> IO (Bool, Bool) -> m (Bool, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    Ptr CInt
xExpand <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr CInt
yExpand <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr TableLayout -> Ptr Actor -> Ptr CInt -> Ptr CInt -> IO ()
clutter_table_layout_get_expand Ptr TableLayout
layout' Ptr Actor
actor' Ptr CInt
xExpand Ptr CInt
yExpand
    CInt
xExpand' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
xExpand
    let xExpand'' :: Bool
xExpand'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
xExpand'
    CInt
yExpand' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
yExpand
    let yExpand'' :: Bool
yExpand'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
yExpand'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
xExpand
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
yExpand
    (Bool, Bool) -> IO (Bool, Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
xExpand'', Bool
yExpand'')

#if defined(ENABLE_OVERLOADING)
data TableLayoutGetExpandMethodInfo
instance (signature ~ (b -> m ((Bool, Bool))), MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod TableLayoutGetExpandMethodInfo a signature where
    overloadedMethod = tableLayoutGetExpand

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


#endif

-- method TableLayout::get_fill
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor child of @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_fill"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the horizontal fill policy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y_fill"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the vertical fill policy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_get_fill" clutter_table_layout_get_fill :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Ptr CInt ->                             -- x_fill : TBasicType TBoolean
    Ptr CInt ->                             -- y_fill : TBasicType TBoolean
    IO ()

{-# DEPRECATED tableLayoutGetFill ["(Since version 1.12)","Use 'GI.Clutter.Objects.Actor.actorGetXAlign' and","  'GI.Clutter.Objects.Actor.actorGetYAlign' instead."] #-}
-- | Retrieves the horizontal and vertical fill policies for /@actor@/
-- as set using 'GI.Clutter.Objects.TableLayout.tableLayoutPack' or 'GI.Clutter.Objects.TableLayout.tableLayoutSetFill'
-- 
-- /Since: 1.4/
tableLayoutGetFill ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> m ((Bool, Bool))
tableLayoutGetFill :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> m (Bool, Bool)
tableLayoutGetFill a
layout b
actor = IO (Bool, Bool) -> m (Bool, Bool)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Bool) -> m (Bool, Bool))
-> IO (Bool, Bool) -> m (Bool, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    Ptr CInt
xFill <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr CInt
yFill <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr TableLayout -> Ptr Actor -> Ptr CInt -> Ptr CInt -> IO ()
clutter_table_layout_get_fill Ptr TableLayout
layout' Ptr Actor
actor' Ptr CInt
xFill Ptr CInt
yFill
    CInt
xFill' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
xFill
    let xFill'' :: Bool
xFill'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
xFill'
    CInt
yFill' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
yFill
    let yFill'' :: Bool
yFill'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
yFill'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
xFill
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
yFill
    (Bool, Bool) -> IO (Bool, Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
xFill'', Bool
yFill'')

#if defined(ENABLE_OVERLOADING)
data TableLayoutGetFillMethodInfo
instance (signature ~ (b -> m ((Bool, Bool))), MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod TableLayoutGetFillMethodInfo a signature where
    overloadedMethod = tableLayoutGetFill

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


#endif

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

foreign import ccall "clutter_table_layout_get_row_count" clutter_table_layout_get_row_count :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    IO Int32

{-# DEPRECATED tableLayoutGetRowCount ["(Since version 1.18)","No direct replacement is available"] #-}
-- | Retrieve the current number rows in the /@layout@/
-- 
-- /Since: 1.4/
tableLayoutGetRowCount ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: A t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> m Int32
    -- ^ __Returns:__ the number of rows
tableLayoutGetRowCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> m Int32
tableLayoutGetRowCount a
layout = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr TableLayout -> IO Int32
clutter_table_layout_get_row_count Ptr TableLayout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TableLayoutGetRowCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutGetRowCountMethodInfo a signature where
    overloadedMethod = tableLayoutGetRowCount

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


#endif

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

{-# DEPRECATED tableLayoutGetRowSpacing ["(Since version 1.18)","Use [GridLayout:rowSpacing](\"GI.Clutter.Objects.GridLayout#g:attr:rowSpacing\") instead"] #-}
-- | Retrieves the spacing set using 'GI.Clutter.Objects.TableLayout.tableLayoutSetRowSpacing'
-- 
-- /Since: 1.4/
tableLayoutGetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> m Word32
    -- ^ __Returns:__ the spacing between rows of the t'GI.Clutter.Objects.TableLayout.TableLayout'
tableLayoutGetRowSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> m Word32
tableLayoutGetRowSpacing 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Word32
result <- Ptr TableLayout -> IO Word32
clutter_table_layout_get_row_spacing Ptr TableLayout
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 TableLayoutGetRowSpacingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutGetRowSpacingMethodInfo a signature where
    overloadedMethod = tableLayoutGetRowSpacing

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


#endif

-- method TableLayout::get_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor child of @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "column_span"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the col span"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "row_span"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the row span"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_get_span" clutter_table_layout_get_span :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Ptr Int32 ->                            -- column_span : TBasicType TInt
    Ptr Int32 ->                            -- row_span : TBasicType TInt
    IO ()

{-# DEPRECATED tableLayoutGetSpan ["(Since version 1.18)","Use the @width@ and @height@ layout properties","  of t'GI.Clutter.Objects.GridLayout.GridLayout' instead"] #-}
-- | Retrieves the row and column span for /@actor@/ as set using
-- 'GI.Clutter.Objects.TableLayout.tableLayoutPack' or 'GI.Clutter.Objects.TableLayout.tableLayoutSetSpan'
-- 
-- /Since: 1.4/
tableLayoutGetSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> m ((Int32, Int32))
tableLayoutGetSpan :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> m (Int32, Int32)
tableLayoutGetSpan a
layout b
actor = IO (Int32, Int32) -> m (Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    Ptr Int32
columnSpan <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
rowSpan <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr TableLayout -> Ptr Actor -> Ptr Int32 -> Ptr Int32 -> IO ()
clutter_table_layout_get_span Ptr TableLayout
layout' Ptr Actor
actor' Ptr Int32
columnSpan Ptr Int32
rowSpan
    Int32
columnSpan' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
columnSpan
    Int32
rowSpan' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
rowSpan
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
columnSpan
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
rowSpan
    (Int32, Int32) -> IO (Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
columnSpan', Int32
rowSpan')

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

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


#endif

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

{-# DEPRECATED tableLayoutGetUseAnimations ["(Since version 1.12)","t'GI.Clutter.Objects.TableLayout.TableLayout' will honour the easing state","  of the children when allocating them. See 'GI.Clutter.Objects.Actor.actorSetEasingMode'","  and 'GI.Clutter.Objects.Actor.actorSetEasingDuration'."] #-}
-- | Retrieves whether /@layout@/ should animate changes in the layout properties
-- 
-- Since 'GI.Clutter.Objects.TableLayout.tableLayoutSetUseAnimations'
-- 
-- /Since: 1.4/
tableLayoutGetUseAnimations ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the animations should be used, 'P.False' otherwise
tableLayoutGetUseAnimations :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> m Bool
tableLayoutGetUseAnimations 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr TableLayout -> IO CInt
clutter_table_layout_get_use_animations Ptr TableLayout
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 TableLayoutGetUseAnimationsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutGetUseAnimationsMethodInfo a signature where
    overloadedMethod = tableLayoutGetUseAnimations

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


#endif

-- method TableLayout::pack
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "column"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the column the @actor should be put, or -1 to append"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "row"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the row the @actor should be put, or -1 to append"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_pack" clutter_table_layout_pack :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Int32 ->                                -- column : TBasicType TInt
    Int32 ->                                -- row : TBasicType TInt
    IO ()

{-# DEPRECATED tableLayoutPack ["(Since version 1.18)","Use 'GI.Clutter.Objects.GridLayout.gridLayoutAttach' instead"] #-}
-- | Packs /@actor@/ inside the t'GI.Clutter.Interfaces.Container.Container' associated to /@layout@/
-- at the given row and column.
-- 
-- /Since: 1.4/
tableLayoutPack ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor'
    -> Int32
    -- ^ /@column@/: the column the /@actor@/ should be put, or -1 to append
    -> Int32
    -- ^ /@row@/: the row the /@actor@/ should be put, or -1 to append
    -> m ()
tableLayoutPack :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> Int32 -> Int32 -> m ()
tableLayoutPack a
layout b
actor Int32
column Int32
row = 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    Ptr TableLayout -> Ptr Actor -> Int32 -> Int32 -> IO ()
clutter_table_layout_pack Ptr TableLayout
layout' Ptr Actor
actor' Int32
column Int32
row
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method TableLayout::set_alignment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor child of @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_align"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableAlignment" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Horizontal alignment policy for @actor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y_align"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableAlignment" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Vertical alignment policy for @actor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_set_alignment" clutter_table_layout_set_alignment :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CUInt ->                                -- x_align : TInterface (Name {namespace = "Clutter", name = "TableAlignment"})
    CUInt ->                                -- y_align : TInterface (Name {namespace = "Clutter", name = "TableAlignment"})
    IO ()

{-# DEPRECATED tableLayoutSetAlignment ["(Since version 1.12)","Use 'GI.Clutter.Objects.Actor.actorSetXAlign' and","  'GI.Clutter.Objects.Actor.actorSetYAlign' instead."] #-}
-- | Sets the horizontal and vertical alignment policies for /@actor@/
-- inside /@layout@/
-- 
-- /Since: 1.4/
tableLayoutSetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> Clutter.Enums.TableAlignment
    -- ^ /@xAlign@/: Horizontal alignment policy for /@actor@/
    -> Clutter.Enums.TableAlignment
    -- ^ /@yAlign@/: Vertical alignment policy for /@actor@/
    -> m ()
tableLayoutSetAlignment :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> TableAlignment -> TableAlignment -> m ()
tableLayoutSetAlignment a
layout b
actor TableAlignment
xAlign TableAlignment
yAlign = 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    let xAlign' :: CUInt
xAlign' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TableAlignment -> Int) -> TableAlignment -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableAlignment -> Int
forall a. Enum a => a -> Int
fromEnum) TableAlignment
xAlign
    let yAlign' :: CUInt
yAlign' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (TableAlignment -> Int) -> TableAlignment -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableAlignment -> Int
forall a. Enum a => a -> Int
fromEnum) TableAlignment
yAlign
    Ptr TableLayout -> Ptr Actor -> CUInt -> CUInt -> IO ()
clutter_table_layout_set_alignment Ptr TableLayout
layout' Ptr Actor
actor' CUInt
xAlign' CUInt
yAlign'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TableLayoutSetAlignmentMethodInfo
instance (signature ~ (b -> Clutter.Enums.TableAlignment -> Clutter.Enums.TableAlignment -> m ()), MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod TableLayoutSetAlignmentMethodInfo a signature where
    overloadedMethod = tableLayoutSetAlignment

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


#endif

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

{-# DEPRECATED tableLayoutSetColumnSpacing ["(Since version 1.18)","Use [GridLayout:columnSpacing](\"GI.Clutter.Objects.GridLayout#g:attr:columnSpacing\") instead"] #-}
-- | Sets the spacing between columns of /@layout@/
-- 
-- /Since: 1.4/
tableLayoutSetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> Word32
    -- ^ /@spacing@/: the spacing between columns of the layout, in pixels
    -> m ()
tableLayoutSetColumnSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> Word32 -> m ()
tableLayoutSetColumnSpacing 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr TableLayout -> Word32 -> IO ()
clutter_table_layout_set_column_spacing Ptr TableLayout
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 TableLayoutSetColumnSpacingMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutSetColumnSpacingMethodInfo a signature where
    overloadedMethod = tableLayoutSetColumnSpacing

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


#endif

-- method TableLayout::set_easing_duration
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "msecs"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the duration of the animations, in milliseconds"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_set_easing_duration" clutter_table_layout_set_easing_duration :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Word32 ->                               -- msecs : TBasicType TUInt
    IO ()

{-# DEPRECATED tableLayoutSetEasingDuration ["(Since version 1.12)","t'GI.Clutter.Objects.TableLayout.TableLayout' will honour the easing state","  of the children when allocating them. See 'GI.Clutter.Objects.Actor.actorSetEasingMode'","  and 'GI.Clutter.Objects.Actor.actorSetEasingDuration'."] #-}
-- | Sets the duration of the animations used by /@layout@/ when animating changes
-- in the layout properties
-- 
-- Use 'GI.Clutter.Objects.TableLayout.tableLayoutSetUseAnimations' to enable and disable the
-- animations
-- 
-- /Since: 1.4/
tableLayoutSetEasingDuration ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> Word32
    -- ^ /@msecs@/: the duration of the animations, in milliseconds
    -> m ()
tableLayoutSetEasingDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> Word32 -> m ()
tableLayoutSetEasingDuration a
layout Word32
msecs = 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr TableLayout -> Word32 -> IO ()
clutter_table_layout_set_easing_duration Ptr TableLayout
layout' Word32
msecs
    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 TableLayoutSetEasingDurationMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutSetEasingDurationMethodInfo a signature where
    overloadedMethod = tableLayoutSetEasingDuration

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


#endif

-- method TableLayout::set_easing_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an easing mode, either from #ClutterAnimationMode or a logical id\n  from clutter_alpha_register_func()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_set_easing_mode" clutter_table_layout_set_easing_mode :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    CULong ->                               -- mode : TBasicType TULong
    IO ()

{-# DEPRECATED tableLayoutSetEasingMode ["(Since version 1.12)","t'GI.Clutter.Objects.TableLayout.TableLayout' will honour the easing state","  of the children when allocating them. See 'GI.Clutter.Objects.Actor.actorSetEasingMode'","  and 'GI.Clutter.Objects.Actor.actorSetEasingDuration'."] #-}
-- | Sets the easing mode to be used by /@layout@/ when animating changes in layout
-- properties
-- 
-- Use 'GI.Clutter.Objects.TableLayout.tableLayoutSetUseAnimations' to enable and disable the
-- animations
-- 
-- /Since: 1.4/
tableLayoutSetEasingMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> CULong
    -- ^ /@mode@/: an easing mode, either from t'GI.Clutter.Enums.AnimationMode' or a logical id
    --   from @/clutter_alpha_register_func()/@
    -> m ()
tableLayoutSetEasingMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> CULong -> m ()
tableLayoutSetEasingMode a
layout CULong
mode = 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr TableLayout -> CULong -> IO ()
clutter_table_layout_set_easing_mode Ptr TableLayout
layout' CULong
mode
    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 TableLayoutSetEasingModeMethodInfo
instance (signature ~ (CULong -> m ()), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutSetEasingModeMethodInfo a signature where
    overloadedMethod = tableLayoutSetEasingMode

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


#endif

-- method TableLayout::set_expand
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor child of @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_expand"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether @actor should allocate extra space horizontally"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y_expand"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether @actor should allocate extra space vertically"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_set_expand" clutter_table_layout_set_expand :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CInt ->                                 -- x_expand : TBasicType TBoolean
    CInt ->                                 -- y_expand : TBasicType TBoolean
    IO ()

{-# DEPRECATED tableLayoutSetExpand ["(Since version 1.12)","Use 'GI.Clutter.Objects.Actor.actorSetXExpand' or","  'GI.Clutter.Objects.Actor.actorSetYExpand' instead."] #-}
-- | Sets the horizontal and vertical expand policies for /@actor@/
-- inside /@layout@/
-- 
-- /Since: 1.4/
tableLayoutSetExpand ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> Bool
    -- ^ /@xExpand@/: whether /@actor@/ should allocate extra space horizontally
    -> Bool
    -- ^ /@yExpand@/: whether /@actor@/ should allocate extra space vertically
    -> m ()
tableLayoutSetExpand :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> Bool -> Bool -> m ()
tableLayoutSetExpand a
layout b
actor Bool
xExpand Bool
yExpand = 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    let xExpand' :: CInt
xExpand' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
xExpand
    let yExpand' :: CInt
yExpand' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
yExpand
    Ptr TableLayout -> Ptr Actor -> CInt -> CInt -> IO ()
clutter_table_layout_set_expand Ptr TableLayout
layout' Ptr Actor
actor' CInt
xExpand' CInt
yExpand'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TableLayoutSetExpandMethodInfo
instance (signature ~ (b -> Bool -> Bool -> m ()), MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod TableLayoutSetExpandMethodInfo a signature where
    overloadedMethod = tableLayoutSetExpand

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


#endif

-- method TableLayout::set_fill
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor child of @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_fill"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether @actor should fill horizontally the allocated space"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y_fill"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether @actor should fill vertically the allocated space"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_set_fill" clutter_table_layout_set_fill :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CInt ->                                 -- x_fill : TBasicType TBoolean
    CInt ->                                 -- y_fill : TBasicType TBoolean
    IO ()

{-# DEPRECATED tableLayoutSetFill ["(Since version 1.12)","Use 'GI.Clutter.Objects.Actor.actorSetXAlign' and","  'GI.Clutter.Objects.Actor.actorSetYAlign' instead."] #-}
-- | Sets the horizontal and vertical fill policies for /@actor@/
-- inside /@layout@/
-- 
-- /Since: 1.4/
tableLayoutSetFill ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> Bool
    -- ^ /@xFill@/: whether /@actor@/ should fill horizontally the allocated space
    -> Bool
    -- ^ /@yFill@/: whether /@actor@/ should fill vertically the allocated space
    -> m ()
tableLayoutSetFill :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> Bool -> Bool -> m ()
tableLayoutSetFill a
layout b
actor Bool
xFill Bool
yFill = 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    let xFill' :: CInt
xFill' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
xFill
    let yFill' :: CInt
yFill' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
yFill
    Ptr TableLayout -> Ptr Actor -> CInt -> CInt -> IO ()
clutter_table_layout_set_fill Ptr TableLayout
layout' Ptr Actor
actor' CInt
xFill' CInt
yFill'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TableLayoutSetFillMethodInfo
instance (signature ~ (b -> Bool -> Bool -> m ()), MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod TableLayoutSetFillMethodInfo a signature where
    overloadedMethod = tableLayoutSetFill

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


#endif

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

{-# DEPRECATED tableLayoutSetRowSpacing ["(Since version 1.18)","Use [GridLayout:rowSpacing](\"GI.Clutter.Objects.GridLayout#g:attr:rowSpacing\") instead"] #-}
-- | Sets the spacing between rows of /@layout@/
-- 
-- /Since: 1.4/
tableLayoutSetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> Word32
    -- ^ /@spacing@/: the spacing between rows of the layout, in pixels
    -> m ()
tableLayoutSetRowSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> Word32 -> m ()
tableLayoutSetRowSpacing 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr TableLayout -> Word32 -> IO ()
clutter_table_layout_set_row_spacing Ptr TableLayout
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 TableLayoutSetRowSpacingMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutSetRowSpacingMethodInfo a signature where
    overloadedMethod = tableLayoutSetRowSpacing

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


#endif

-- method TableLayout::set_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "actor"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "Actor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterActor child of @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "column_span"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Column span for @actor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "row_span"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Row span for @actor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_set_span" clutter_table_layout_set_span :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Int32 ->                                -- column_span : TBasicType TInt
    Int32 ->                                -- row_span : TBasicType TInt
    IO ()

{-# DEPRECATED tableLayoutSetSpan ["(Since version 1.18)","Use the @width@ and @height@ layout properties","  of t'GI.Clutter.Objects.GridLayout.GridLayout' instead"] #-}
-- | Sets the row and column span for /@actor@/
-- inside /@layout@/
-- 
-- /Since: 1.4/
tableLayoutSetSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> Int32
    -- ^ /@columnSpan@/: Column span for /@actor@/
    -> Int32
    -- ^ /@rowSpan@/: Row span for /@actor@/
    -> m ()
tableLayoutSetSpan :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsTableLayout a, IsActor b) =>
a -> b -> Int32 -> Int32 -> m ()
tableLayoutSetSpan a
layout b
actor Int32
columnSpan Int32
rowSpan = 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Actor
actor' <- b -> IO (Ptr Actor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
actor
    Ptr TableLayout -> Ptr Actor -> Int32 -> Int32 -> IO ()
clutter_table_layout_set_span Ptr TableLayout
layout' Ptr Actor
actor' Int32
columnSpan Int32
rowSpan
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method TableLayout::set_use_animations
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "TableLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterTableLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "animate"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE if the @layout should use animations"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_table_layout_set_use_animations" clutter_table_layout_set_use_animations :: 
    Ptr TableLayout ->                      -- layout : TInterface (Name {namespace = "Clutter", name = "TableLayout"})
    CInt ->                                 -- animate : TBasicType TBoolean
    IO ()

{-# DEPRECATED tableLayoutSetUseAnimations ["(Since version 1.12)","t'GI.Clutter.Objects.TableLayout.TableLayout' will honour the easing state","  of the children when allocating them. See 'GI.Clutter.Objects.Actor.actorSetEasingMode'","  and 'GI.Clutter.Objects.Actor.actorSetEasingDuration'."] #-}
-- | Sets whether /@layout@/ should animate changes in the layout properties
-- 
-- The duration of the animations is controlled by
-- 'GI.Clutter.Objects.TableLayout.tableLayoutSetEasingDuration'; the easing mode to be used
-- by the animations is controlled by 'GI.Clutter.Objects.TableLayout.tableLayoutSetEasingMode'
-- 
-- /Since: 1.4/
tableLayoutSetUseAnimations ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.TableLayout.TableLayout'
    -> Bool
    -- ^ /@animate@/: 'P.True' if the /@layout@/ should use animations
    -> m ()
tableLayoutSetUseAnimations :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTableLayout a) =>
a -> Bool -> m ()
tableLayoutSetUseAnimations a
layout Bool
animate = 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 TableLayout
layout' <- a -> IO (Ptr TableLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let animate' :: CInt
animate' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
animate
    Ptr TableLayout -> CInt -> IO ()
clutter_table_layout_set_use_animations Ptr TableLayout
layout' CInt
animate'
    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 TableLayoutSetUseAnimationsMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTableLayout a) => O.OverloadedMethod TableLayoutSetUseAnimationsMethodInfo a signature where
    overloadedMethod = tableLayoutSetUseAnimations

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


#endif