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

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

module GI.Clutter.Objects.BoxLayout
    ( 

-- * Exported types
    BoxLayout(..)                           ,
    IsBoxLayout                             ,
    toBoxLayout                             ,


 -- * 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.BoxLayout#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.BoxLayout#g:method:getAlignment"), [getAnimationProgress]("GI.Clutter.Objects.LayoutManager#g:method:getAnimationProgress"), [getChildMeta]("GI.Clutter.Objects.LayoutManager#g:method:getChildMeta"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getEasingDuration]("GI.Clutter.Objects.BoxLayout#g:method:getEasingDuration"), [getEasingMode]("GI.Clutter.Objects.BoxLayout#g:method:getEasingMode"), [getExpand]("GI.Clutter.Objects.BoxLayout#g:method:getExpand"), [getFill]("GI.Clutter.Objects.BoxLayout#g:method:getFill"), [getHomogeneous]("GI.Clutter.Objects.BoxLayout#g:method:getHomogeneous"), [getOrientation]("GI.Clutter.Objects.BoxLayout#g:method:getOrientation"), [getPackStart]("GI.Clutter.Objects.BoxLayout#g:method:getPackStart"), [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"), [getSpacing]("GI.Clutter.Objects.BoxLayout#g:method:getSpacing"), [getUseAnimations]("GI.Clutter.Objects.BoxLayout#g:method:getUseAnimations"), [getVertical]("GI.Clutter.Objects.BoxLayout#g:method:getVertical").
-- 
-- ==== Setters
-- [setAlignment]("GI.Clutter.Objects.BoxLayout#g:method:setAlignment"), [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.BoxLayout#g:method:setEasingDuration"), [setEasingMode]("GI.Clutter.Objects.BoxLayout#g:method:setEasingMode"), [setExpand]("GI.Clutter.Objects.BoxLayout#g:method:setExpand"), [setFill]("GI.Clutter.Objects.BoxLayout#g:method:setFill"), [setHomogeneous]("GI.Clutter.Objects.BoxLayout#g:method:setHomogeneous"), [setOrientation]("GI.Clutter.Objects.BoxLayout#g:method:setOrientation"), [setPackStart]("GI.Clutter.Objects.BoxLayout#g:method:setPackStart"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSpacing]("GI.Clutter.Objects.BoxLayout#g:method:setSpacing"), [setUseAnimations]("GI.Clutter.Objects.BoxLayout#g:method:setUseAnimations"), [setVertical]("GI.Clutter.Objects.BoxLayout#g:method:setVertical").

#if defined(ENABLE_OVERLOADING)
    ResolveBoxLayoutMethod                  ,
#endif

-- ** getAlignment #method:getAlignment#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetAlignmentMethodInfo         ,
#endif
    boxLayoutGetAlignment                   ,


-- ** getEasingDuration #method:getEasingDuration#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetEasingDurationMethodInfo    ,
#endif
    boxLayoutGetEasingDuration              ,


-- ** getEasingMode #method:getEasingMode#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetEasingModeMethodInfo        ,
#endif
    boxLayoutGetEasingMode                  ,


-- ** getExpand #method:getExpand#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetExpandMethodInfo            ,
#endif
    boxLayoutGetExpand                      ,


-- ** getFill #method:getFill#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetFillMethodInfo              ,
#endif
    boxLayoutGetFill                        ,


-- ** getHomogeneous #method:getHomogeneous#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetHomogeneousMethodInfo       ,
#endif
    boxLayoutGetHomogeneous                 ,


-- ** getOrientation #method:getOrientation#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetOrientationMethodInfo       ,
#endif
    boxLayoutGetOrientation                 ,


-- ** getPackStart #method:getPackStart#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetPackStartMethodInfo         ,
#endif
    boxLayoutGetPackStart                   ,


-- ** getSpacing #method:getSpacing#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetSpacingMethodInfo           ,
#endif
    boxLayoutGetSpacing                     ,


-- ** getUseAnimations #method:getUseAnimations#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetUseAnimationsMethodInfo     ,
#endif
    boxLayoutGetUseAnimations               ,


-- ** getVertical #method:getVertical#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutGetVerticalMethodInfo          ,
#endif
    boxLayoutGetVertical                    ,


-- ** new #method:new#

    boxLayoutNew                            ,


-- ** pack #method:pack#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutPackMethodInfo                 ,
#endif
    boxLayoutPack                           ,


-- ** setAlignment #method:setAlignment#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetAlignmentMethodInfo         ,
#endif
    boxLayoutSetAlignment                   ,


-- ** setEasingDuration #method:setEasingDuration#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetEasingDurationMethodInfo    ,
#endif
    boxLayoutSetEasingDuration              ,


-- ** setEasingMode #method:setEasingMode#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetEasingModeMethodInfo        ,
#endif
    boxLayoutSetEasingMode                  ,


-- ** setExpand #method:setExpand#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetExpandMethodInfo            ,
#endif
    boxLayoutSetExpand                      ,


-- ** setFill #method:setFill#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetFillMethodInfo              ,
#endif
    boxLayoutSetFill                        ,


-- ** setHomogeneous #method:setHomogeneous#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetHomogeneousMethodInfo       ,
#endif
    boxLayoutSetHomogeneous                 ,


-- ** setOrientation #method:setOrientation#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetOrientationMethodInfo       ,
#endif
    boxLayoutSetOrientation                 ,


-- ** setPackStart #method:setPackStart#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetPackStartMethodInfo         ,
#endif
    boxLayoutSetPackStart                   ,


-- ** setSpacing #method:setSpacing#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetSpacingMethodInfo           ,
#endif
    boxLayoutSetSpacing                     ,


-- ** setUseAnimations #method:setUseAnimations#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetUseAnimationsMethodInfo     ,
#endif
    boxLayoutSetUseAnimations               ,


-- ** setVertical #method:setVertical#

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSetVerticalMethodInfo          ,
#endif
    boxLayoutSetVertical                    ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    BoxLayoutEasingDurationPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxLayoutEasingDuration                 ,
#endif
    constructBoxLayoutEasingDuration        ,
    getBoxLayoutEasingDuration              ,
    setBoxLayoutEasingDuration              ,


-- ** easingMode #attr:easingMode#
-- | The easing mode for the animations, in case
-- [BoxLayout:useAnimations]("GI.Clutter.Objects.BoxLayout#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.2/

#if defined(ENABLE_OVERLOADING)
    BoxLayoutEasingModePropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxLayoutEasingMode                     ,
#endif
    constructBoxLayoutEasingMode            ,
    getBoxLayoutEasingMode                  ,
    setBoxLayoutEasingMode                  ,


-- ** homogeneous #attr:homogeneous#
-- | Whether the t'GI.Clutter.Objects.BoxLayout.BoxLayout' should arrange its children
-- homogeneously, i.e. all children get the same size
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    BoxLayoutHomogeneousPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxLayoutHomogeneous                    ,
#endif
    constructBoxLayoutHomogeneous           ,
    getBoxLayoutHomogeneous                 ,
    setBoxLayoutHomogeneous                 ,


-- ** orientation #attr:orientation#
-- | The orientation of the t'GI.Clutter.Objects.BoxLayout.BoxLayout', either horizontal
-- or vertical
-- 
-- /Since: 1.12/

#if defined(ENABLE_OVERLOADING)
    BoxLayoutOrientationPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxLayoutOrientation                    ,
#endif
    constructBoxLayoutOrientation           ,
    getBoxLayoutOrientation                 ,
    setBoxLayoutOrientation                 ,


-- ** packStart #attr:packStart#
-- | Whether the t'GI.Clutter.Objects.BoxLayout.BoxLayout' should pack items at the start
-- or append them at the end
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    BoxLayoutPackStartPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxLayoutPackStart                      ,
#endif
    constructBoxLayoutPackStart             ,
    getBoxLayoutPackStart                   ,
    setBoxLayoutPackStart                   ,


-- ** spacing #attr:spacing#
-- | The spacing between children of the t'GI.Clutter.Objects.BoxLayout.BoxLayout', in pixels
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    BoxLayoutSpacingPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxLayoutSpacing                        ,
#endif
    constructBoxLayoutSpacing               ,
    getBoxLayoutSpacing                     ,
    setBoxLayoutSpacing                     ,


-- ** useAnimations #attr:useAnimations#
-- | Whether the t'GI.Clutter.Objects.BoxLayout.BoxLayout' should animate changes in the
-- layout, overriding the easing state of the children.
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    BoxLayoutUseAnimationsPropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxLayoutUseAnimations                  ,
#endif
    constructBoxLayoutUseAnimations         ,
    getBoxLayoutUseAnimations               ,
    setBoxLayoutUseAnimations               ,


-- ** vertical #attr:vertical#
-- | Whether the t'GI.Clutter.Objects.BoxLayout.BoxLayout' should arrange its children
-- alongside the Y axis, instead of alongside the X axis
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    BoxLayoutVerticalPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxLayoutVertical                       ,
#endif
    constructBoxLayoutVertical              ,
    getBoxLayoutVertical                    ,
    setBoxLayoutVertical                    ,




    ) 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 BoxLayout = BoxLayout (SP.ManagedPtr BoxLayout)
    deriving (BoxLayout -> BoxLayout -> Bool
(BoxLayout -> BoxLayout -> Bool)
-> (BoxLayout -> BoxLayout -> Bool) -> Eq BoxLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BoxLayout -> BoxLayout -> Bool
== :: BoxLayout -> BoxLayout -> Bool
$c/= :: BoxLayout -> BoxLayout -> Bool
/= :: BoxLayout -> BoxLayout -> Bool
Eq)

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

foreign import ccall "clutter_box_layout_get_type"
    c_clutter_box_layout_get_type :: IO B.Types.GType

instance B.Types.TypedObject BoxLayout where
    glibType :: IO GType
glibType = IO GType
c_clutter_box_layout_get_type

instance B.Types.GObject BoxLayout

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveBoxLayoutMethod (t :: Symbol) (o :: *) :: * where
    ResolveBoxLayoutMethod "allocate" o = Clutter.LayoutManager.LayoutManagerAllocateMethodInfo
    ResolveBoxLayoutMethod "beginAnimation" o = Clutter.LayoutManager.LayoutManagerBeginAnimationMethodInfo
    ResolveBoxLayoutMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBoxLayoutMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBoxLayoutMethod "childGetProperty" o = Clutter.LayoutManager.LayoutManagerChildGetPropertyMethodInfo
    ResolveBoxLayoutMethod "childSetProperty" o = Clutter.LayoutManager.LayoutManagerChildSetPropertyMethodInfo
    ResolveBoxLayoutMethod "endAnimation" o = Clutter.LayoutManager.LayoutManagerEndAnimationMethodInfo
    ResolveBoxLayoutMethod "findChildProperty" o = Clutter.LayoutManager.LayoutManagerFindChildPropertyMethodInfo
    ResolveBoxLayoutMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBoxLayoutMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBoxLayoutMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBoxLayoutMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveBoxLayoutMethod "layoutChanged" o = Clutter.LayoutManager.LayoutManagerLayoutChangedMethodInfo
    ResolveBoxLayoutMethod "listChildProperties" o = Clutter.LayoutManager.LayoutManagerListChildPropertiesMethodInfo
    ResolveBoxLayoutMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveBoxLayoutMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveBoxLayoutMethod "pack" o = BoxLayoutPackMethodInfo
    ResolveBoxLayoutMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBoxLayoutMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBoxLayoutMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveBoxLayoutMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveBoxLayoutMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveBoxLayoutMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveBoxLayoutMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveBoxLayoutMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBoxLayoutMethod "getAlignment" o = BoxLayoutGetAlignmentMethodInfo
    ResolveBoxLayoutMethod "getAnimationProgress" o = Clutter.LayoutManager.LayoutManagerGetAnimationProgressMethodInfo
    ResolveBoxLayoutMethod "getChildMeta" o = Clutter.LayoutManager.LayoutManagerGetChildMetaMethodInfo
    ResolveBoxLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveBoxLayoutMethod "getEasingDuration" o = BoxLayoutGetEasingDurationMethodInfo
    ResolveBoxLayoutMethod "getEasingMode" o = BoxLayoutGetEasingModeMethodInfo
    ResolveBoxLayoutMethod "getExpand" o = BoxLayoutGetExpandMethodInfo
    ResolveBoxLayoutMethod "getFill" o = BoxLayoutGetFillMethodInfo
    ResolveBoxLayoutMethod "getHomogeneous" o = BoxLayoutGetHomogeneousMethodInfo
    ResolveBoxLayoutMethod "getOrientation" o = BoxLayoutGetOrientationMethodInfo
    ResolveBoxLayoutMethod "getPackStart" o = BoxLayoutGetPackStartMethodInfo
    ResolveBoxLayoutMethod "getPreferredHeight" o = Clutter.LayoutManager.LayoutManagerGetPreferredHeightMethodInfo
    ResolveBoxLayoutMethod "getPreferredWidth" o = Clutter.LayoutManager.LayoutManagerGetPreferredWidthMethodInfo
    ResolveBoxLayoutMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveBoxLayoutMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveBoxLayoutMethod "getSpacing" o = BoxLayoutGetSpacingMethodInfo
    ResolveBoxLayoutMethod "getUseAnimations" o = BoxLayoutGetUseAnimationsMethodInfo
    ResolveBoxLayoutMethod "getVertical" o = BoxLayoutGetVerticalMethodInfo
    ResolveBoxLayoutMethod "setAlignment" o = BoxLayoutSetAlignmentMethodInfo
    ResolveBoxLayoutMethod "setContainer" o = Clutter.LayoutManager.LayoutManagerSetContainerMethodInfo
    ResolveBoxLayoutMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveBoxLayoutMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveBoxLayoutMethod "setEasingDuration" o = BoxLayoutSetEasingDurationMethodInfo
    ResolveBoxLayoutMethod "setEasingMode" o = BoxLayoutSetEasingModeMethodInfo
    ResolveBoxLayoutMethod "setExpand" o = BoxLayoutSetExpandMethodInfo
    ResolveBoxLayoutMethod "setFill" o = BoxLayoutSetFillMethodInfo
    ResolveBoxLayoutMethod "setHomogeneous" o = BoxLayoutSetHomogeneousMethodInfo
    ResolveBoxLayoutMethod "setOrientation" o = BoxLayoutSetOrientationMethodInfo
    ResolveBoxLayoutMethod "setPackStart" o = BoxLayoutSetPackStartMethodInfo
    ResolveBoxLayoutMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveBoxLayoutMethod "setSpacing" o = BoxLayoutSetSpacingMethodInfo
    ResolveBoxLayoutMethod "setUseAnimations" o = BoxLayoutSetUseAnimationsMethodInfo
    ResolveBoxLayoutMethod "setVertical" o = BoxLayoutSetVerticalMethodInfo
    ResolveBoxLayoutMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#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' boxLayout #easingDuration
-- @
getBoxLayoutEasingDuration :: (MonadIO m, IsBoxLayout o) => o -> m Word32
getBoxLayoutEasingDuration :: forall (m :: * -> *) o. (MonadIO m, IsBoxLayout o) => o -> m Word32
getBoxLayoutEasingDuration 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' boxLayout [ #easingDuration 'Data.GI.Base.Attributes.:=' value ]
-- @
setBoxLayoutEasingDuration :: (MonadIO m, IsBoxLayout o) => o -> Word32 -> m ()
setBoxLayoutEasingDuration :: forall (m :: * -> *) o.
(MonadIO m, IsBoxLayout o) =>
o -> Word32 -> m ()
setBoxLayoutEasingDuration 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`.
constructBoxLayoutEasingDuration :: (IsBoxLayout o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructBoxLayoutEasingDuration :: forall o (m :: * -> *).
(IsBoxLayout o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructBoxLayoutEasingDuration 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 BoxLayoutEasingDurationPropertyInfo
instance AttrInfo BoxLayoutEasingDurationPropertyInfo where
    type AttrAllowedOps BoxLayoutEasingDurationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxLayoutEasingDurationPropertyInfo = IsBoxLayout
    type AttrSetTypeConstraint BoxLayoutEasingDurationPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint BoxLayoutEasingDurationPropertyInfo = (~) Word32
    type AttrTransferType BoxLayoutEasingDurationPropertyInfo = Word32
    type AttrGetType BoxLayoutEasingDurationPropertyInfo = Word32
    type AttrLabel BoxLayoutEasingDurationPropertyInfo = "easing-duration"
    type AttrOrigin BoxLayoutEasingDurationPropertyInfo = BoxLayout
    attrGet = getBoxLayoutEasingDuration
    attrSet = setBoxLayoutEasingDuration
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxLayoutEasingDuration
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BoxLayout.easingDuration"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-BoxLayout.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' boxLayout #easingMode
-- @
getBoxLayoutEasingMode :: (MonadIO m, IsBoxLayout o) => o -> m CULong
getBoxLayoutEasingMode :: forall (m :: * -> *) o. (MonadIO m, IsBoxLayout o) => o -> m CULong
getBoxLayoutEasingMode 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' boxLayout [ #easingMode 'Data.GI.Base.Attributes.:=' value ]
-- @
setBoxLayoutEasingMode :: (MonadIO m, IsBoxLayout o) => o -> CULong -> m ()
setBoxLayoutEasingMode :: forall (m :: * -> *) o.
(MonadIO m, IsBoxLayout o) =>
o -> CULong -> m ()
setBoxLayoutEasingMode 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`.
constructBoxLayoutEasingMode :: (IsBoxLayout o, MIO.MonadIO m) => CULong -> m (GValueConstruct o)
constructBoxLayoutEasingMode :: forall o (m :: * -> *).
(IsBoxLayout o, MonadIO m) =>
CULong -> m (GValueConstruct o)
constructBoxLayoutEasingMode 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 BoxLayoutEasingModePropertyInfo
instance AttrInfo BoxLayoutEasingModePropertyInfo where
    type AttrAllowedOps BoxLayoutEasingModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxLayoutEasingModePropertyInfo = IsBoxLayout
    type AttrSetTypeConstraint BoxLayoutEasingModePropertyInfo = (~) CULong
    type AttrTransferTypeConstraint BoxLayoutEasingModePropertyInfo = (~) CULong
    type AttrTransferType BoxLayoutEasingModePropertyInfo = CULong
    type AttrGetType BoxLayoutEasingModePropertyInfo = CULong
    type AttrLabel BoxLayoutEasingModePropertyInfo = "easing-mode"
    type AttrOrigin BoxLayoutEasingModePropertyInfo = BoxLayout
    attrGet = getBoxLayoutEasingMode
    attrSet = setBoxLayoutEasingMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxLayoutEasingMode
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BoxLayout.easingMode"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-BoxLayout.html#g:attr:easingMode"
        })
#endif

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

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

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

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

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data BoxLayoutOrientationPropertyInfo
instance AttrInfo BoxLayoutOrientationPropertyInfo where
    type AttrAllowedOps BoxLayoutOrientationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxLayoutOrientationPropertyInfo = IsBoxLayout
    type AttrSetTypeConstraint BoxLayoutOrientationPropertyInfo = (~) Clutter.Enums.Orientation
    type AttrTransferTypeConstraint BoxLayoutOrientationPropertyInfo = (~) Clutter.Enums.Orientation
    type AttrTransferType BoxLayoutOrientationPropertyInfo = Clutter.Enums.Orientation
    type AttrGetType BoxLayoutOrientationPropertyInfo = Clutter.Enums.Orientation
    type AttrLabel BoxLayoutOrientationPropertyInfo = "orientation"
    type AttrOrigin BoxLayoutOrientationPropertyInfo = BoxLayout
    attrGet = getBoxLayoutOrientation
    attrSet = setBoxLayoutOrientation
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxLayoutOrientation
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BoxLayout.orientation"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-BoxLayout.html#g:attr:orientation"
        })
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data BoxLayoutPackStartPropertyInfo
instance AttrInfo BoxLayoutPackStartPropertyInfo where
    type AttrAllowedOps BoxLayoutPackStartPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxLayoutPackStartPropertyInfo = IsBoxLayout
    type AttrSetTypeConstraint BoxLayoutPackStartPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint BoxLayoutPackStartPropertyInfo = (~) Bool
    type AttrTransferType BoxLayoutPackStartPropertyInfo = Bool
    type AttrGetType BoxLayoutPackStartPropertyInfo = Bool
    type AttrLabel BoxLayoutPackStartPropertyInfo = "pack-start"
    type AttrOrigin BoxLayoutPackStartPropertyInfo = BoxLayout
    attrGet = getBoxLayoutPackStart
    attrSet = setBoxLayoutPackStart
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxLayoutPackStart
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BoxLayout.packStart"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-BoxLayout.html#g:attr:packStart"
        })
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data BoxLayoutSpacingPropertyInfo
instance AttrInfo BoxLayoutSpacingPropertyInfo where
    type AttrAllowedOps BoxLayoutSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxLayoutSpacingPropertyInfo = IsBoxLayout
    type AttrSetTypeConstraint BoxLayoutSpacingPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint BoxLayoutSpacingPropertyInfo = (~) Word32
    type AttrTransferType BoxLayoutSpacingPropertyInfo = Word32
    type AttrGetType BoxLayoutSpacingPropertyInfo = Word32
    type AttrLabel BoxLayoutSpacingPropertyInfo = "spacing"
    type AttrOrigin BoxLayoutSpacingPropertyInfo = BoxLayout
    attrGet = getBoxLayoutSpacing
    attrSet = setBoxLayoutSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxLayoutSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BoxLayout.spacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-BoxLayout.html#g:attr:spacing"
        })
#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' boxLayout #useAnimations
-- @
getBoxLayoutUseAnimations :: (MonadIO m, IsBoxLayout o) => o -> m Bool
getBoxLayoutUseAnimations :: forall (m :: * -> *) o. (MonadIO m, IsBoxLayout o) => o -> m Bool
getBoxLayoutUseAnimations 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' boxLayout [ #useAnimations 'Data.GI.Base.Attributes.:=' value ]
-- @
setBoxLayoutUseAnimations :: (MonadIO m, IsBoxLayout o) => o -> Bool -> m ()
setBoxLayoutUseAnimations :: forall (m :: * -> *) o.
(MonadIO m, IsBoxLayout o) =>
o -> Bool -> m ()
setBoxLayoutUseAnimations 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`.
constructBoxLayoutUseAnimations :: (IsBoxLayout o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructBoxLayoutUseAnimations :: forall o (m :: * -> *).
(IsBoxLayout o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructBoxLayoutUseAnimations 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 BoxLayoutUseAnimationsPropertyInfo
instance AttrInfo BoxLayoutUseAnimationsPropertyInfo where
    type AttrAllowedOps BoxLayoutUseAnimationsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxLayoutUseAnimationsPropertyInfo = IsBoxLayout
    type AttrSetTypeConstraint BoxLayoutUseAnimationsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint BoxLayoutUseAnimationsPropertyInfo = (~) Bool
    type AttrTransferType BoxLayoutUseAnimationsPropertyInfo = Bool
    type AttrGetType BoxLayoutUseAnimationsPropertyInfo = Bool
    type AttrLabel BoxLayoutUseAnimationsPropertyInfo = "use-animations"
    type AttrOrigin BoxLayoutUseAnimationsPropertyInfo = BoxLayout
    attrGet = getBoxLayoutUseAnimations
    attrSet = setBoxLayoutUseAnimations
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxLayoutUseAnimations
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.BoxLayout.useAnimations"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-BoxLayout.html#g:attr:useAnimations"
        })
#endif

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BoxLayout
type instance O.AttributeList BoxLayout = BoxLayoutAttributeList
type BoxLayoutAttributeList = ('[ '("easingDuration", BoxLayoutEasingDurationPropertyInfo), '("easingMode", BoxLayoutEasingModePropertyInfo), '("homogeneous", BoxLayoutHomogeneousPropertyInfo), '("orientation", BoxLayoutOrientationPropertyInfo), '("packStart", BoxLayoutPackStartPropertyInfo), '("spacing", BoxLayoutSpacingPropertyInfo), '("useAnimations", BoxLayoutUseAnimationsPropertyInfo), '("vertical", BoxLayoutVerticalPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
boxLayoutEasingDuration :: AttrLabelProxy "easingDuration"
boxLayoutEasingDuration = AttrLabelProxy

boxLayoutEasingMode :: AttrLabelProxy "easingMode"
boxLayoutEasingMode = AttrLabelProxy

boxLayoutHomogeneous :: AttrLabelProxy "homogeneous"
boxLayoutHomogeneous = AttrLabelProxy

boxLayoutOrientation :: AttrLabelProxy "orientation"
boxLayoutOrientation = AttrLabelProxy

boxLayoutPackStart :: AttrLabelProxy "packStart"
boxLayoutPackStart = AttrLabelProxy

boxLayoutSpacing :: AttrLabelProxy "spacing"
boxLayoutSpacing = AttrLabelProxy

boxLayoutUseAnimations :: AttrLabelProxy "useAnimations"
boxLayoutUseAnimations = AttrLabelProxy

boxLayoutVertical :: AttrLabelProxy "vertical"
boxLayoutVertical = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "clutter_box_layout_new" clutter_box_layout_new :: 
    IO (Ptr BoxLayout)

-- | Creates a new t'GI.Clutter.Objects.BoxLayout.BoxLayout' layout manager
-- 
-- /Since: 1.2/
boxLayoutNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m BoxLayout
    -- ^ __Returns:__ the newly created t'GI.Clutter.Objects.BoxLayout.BoxLayout'
boxLayoutNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m BoxLayout
boxLayoutNew  = IO BoxLayout -> m BoxLayout
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BoxLayout -> m BoxLayout) -> IO BoxLayout -> m BoxLayout
forall a b. (a -> b) -> a -> b
$ do
    Ptr BoxLayout
result <- IO (Ptr BoxLayout)
clutter_box_layout_new
    Text -> Ptr BoxLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"boxLayoutNew" Ptr BoxLayout
result
    BoxLayout
result' <- ((ManagedPtr BoxLayout -> BoxLayout)
-> Ptr BoxLayout -> IO BoxLayout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr BoxLayout -> BoxLayout
BoxLayout) Ptr BoxLayout
result
    BoxLayout -> IO BoxLayout
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BoxLayout
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method BoxLayout::get_alignment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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 = "BoxAlignment" }
--           , 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 = "BoxAlignment" }
--           , 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_box_layout_get_alignment" clutter_box_layout_get_alignment :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    Ptr CUInt ->                            -- x_align : TInterface (Name {namespace = "Clutter", name = "BoxAlignment"})
    Ptr CUInt ->                            -- y_align : TInterface (Name {namespace = "Clutter", name = "BoxAlignment"})
    IO ()

{-# DEPRECATED boxLayoutGetAlignment ["(Since version 1.12)","t'GI.Clutter.Objects.BoxLayout.BoxLayout' will honour t'GI.Clutter.Objects.Actor.Actor'\\'s","  [Actor:xAlign](\"GI.Clutter.Objects.Actor#g:attr:xAlign\") and [Actor:yAlign](\"GI.Clutter.Objects.Actor#g:attr:yAlign\") properies"] #-}
-- | Retrieves the horizontal and vertical alignment policies for /@actor@/
-- as set using 'GI.Clutter.Objects.BoxLayout.boxLayoutPack' or 'GI.Clutter.Objects.BoxLayout.boxLayoutSetAlignment'
-- 
-- /Since: 1.2/
boxLayoutGetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> m ((Clutter.Enums.BoxAlignment, Clutter.Enums.BoxAlignment))
boxLayoutGetAlignment :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBoxLayout a, IsActor b) =>
a -> b -> m (BoxAlignment, BoxAlignment)
boxLayoutGetAlignment a
layout b
actor = IO (BoxAlignment, BoxAlignment) -> m (BoxAlignment, BoxAlignment)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (BoxAlignment, BoxAlignment) -> m (BoxAlignment, BoxAlignment))
-> IO (BoxAlignment, BoxAlignment)
-> m (BoxAlignment, BoxAlignment)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
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 BoxLayout -> Ptr Actor -> Ptr CUInt -> Ptr CUInt -> IO ()
clutter_box_layout_get_alignment Ptr BoxLayout
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'' :: BoxAlignment
xAlign'' = (Int -> BoxAlignment
forall a. Enum a => Int -> a
toEnum (Int -> BoxAlignment) -> (CUInt -> Int) -> CUInt -> BoxAlignment
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'' :: BoxAlignment
yAlign'' = (Int -> BoxAlignment
forall a. Enum a => Int -> a
toEnum (Int -> BoxAlignment) -> (CUInt -> Int) -> CUInt -> BoxAlignment
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
    (BoxAlignment, BoxAlignment) -> IO (BoxAlignment, BoxAlignment)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (BoxAlignment
xAlign'', BoxAlignment
yAlign'')

#if defined(ENABLE_OVERLOADING)
data BoxLayoutGetAlignmentMethodInfo
instance (signature ~ (b -> m ((Clutter.Enums.BoxAlignment, Clutter.Enums.BoxAlignment))), MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod BoxLayoutGetAlignmentMethodInfo a signature where
    overloadedMethod = boxLayoutGetAlignment

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


#endif

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

{-# DEPRECATED boxLayoutGetEasingDuration ["(Since version 1.12)"] #-}
-- | Retrieves the duration set using 'GI.Clutter.Objects.BoxLayout.boxLayoutSetEasingDuration'
-- 
-- /Since: 1.2/
boxLayoutGetEasingDuration ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m Word32
    -- ^ __Returns:__ the duration of the animations, in milliseconds
boxLayoutGetEasingDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> m Word32
boxLayoutGetEasingDuration 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Word32
result <- Ptr BoxLayout -> IO Word32
clutter_box_layout_get_easing_duration Ptr BoxLayout
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 BoxLayoutGetEasingDurationMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutGetEasingDurationMethodInfo a signature where
    overloadedMethod = boxLayoutGetEasingDuration

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


#endif

-- method BoxLayout::get_easing_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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_box_layout_get_easing_mode" clutter_box_layout_get_easing_mode :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    IO CULong

{-# DEPRECATED boxLayoutGetEasingMode ["(Since version 1.12)"] #-}
-- | Retrieves the easing mode set using 'GI.Clutter.Objects.BoxLayout.boxLayoutSetEasingMode'
-- 
-- /Since: 1.2/
boxLayoutGetEasingMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m CULong
    -- ^ __Returns:__ an easing mode
boxLayoutGetEasingMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> m CULong
boxLayoutGetEasingMode 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CULong
result <- Ptr BoxLayout -> IO CULong
clutter_box_layout_get_easing_mode Ptr BoxLayout
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 BoxLayoutGetEasingModeMethodInfo
instance (signature ~ (m CULong), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutGetEasingModeMethodInfo a signature where
    overloadedMethod = boxLayoutGetEasingMode

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


#endif

-- method BoxLayout::get_expand
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "clutter_box_layout_get_expand" clutter_box_layout_get_expand :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    IO CInt

{-# DEPRECATED boxLayoutGetExpand ["(Since version 1.12)","t'GI.Clutter.Objects.BoxLayout.BoxLayout' will honour t'GI.Clutter.Objects.Actor.Actor'\\'s","  [Actor:xExpand](\"GI.Clutter.Objects.Actor#g:attr:xExpand\") and [Actor:yExpand](\"GI.Clutter.Objects.Actor#g:attr:yExpand\") properies"] #-}
-- | Retrieves whether /@actor@/ should expand inside /@layout@/
-- 
-- /Since: 1.2/
boxLayoutGetExpand ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the t'GI.Clutter.Objects.Actor.Actor' should expand, 'P.False' otherwise
boxLayoutGetExpand :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBoxLayout a, IsActor b) =>
a -> b -> m Bool
boxLayoutGetExpand a
layout b
actor = 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
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
    CInt
result <- Ptr BoxLayout -> Ptr Actor -> IO CInt
clutter_box_layout_get_expand Ptr BoxLayout
layout' Ptr Actor
actor'
    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
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
actor
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

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

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


#endif

-- method BoxLayout::get_fill
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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_box_layout_get_fill" clutter_box_layout_get_fill :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    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 boxLayoutGetFill ["(Since version 1.12)","t'GI.Clutter.Objects.BoxLayout.BoxLayout' will honour t'GI.Clutter.Objects.Actor.Actor'\\'s","  [Actor:xAlign](\"GI.Clutter.Objects.Actor#g:attr:xAlign\") and [Actor:yAlign](\"GI.Clutter.Objects.Actor#g:attr:yAlign\") properies"] #-}
-- | Retrieves the horizontal and vertical fill policies for /@actor@/
-- as set using 'GI.Clutter.Objects.BoxLayout.boxLayoutPack' or 'GI.Clutter.Objects.BoxLayout.boxLayoutSetFill'
-- 
-- /Since: 1.2/
boxLayoutGetFill ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> m ((Bool, Bool))
boxLayoutGetFill :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBoxLayout a, IsActor b) =>
a -> b -> m (Bool, Bool)
boxLayoutGetFill 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
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 BoxLayout -> Ptr Actor -> Ptr CInt -> Ptr CInt -> IO ()
clutter_box_layout_get_fill Ptr BoxLayout
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 BoxLayoutGetFillMethodInfo
instance (signature ~ (b -> m ((Bool, Bool))), MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod BoxLayoutGetFillMethodInfo a signature where
    overloadedMethod = boxLayoutGetFill

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


#endif

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

-- | Retrieves if the children sizes are allocated homogeneously.
-- 
-- /Since: 1.4/
boxLayoutGetHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the t'GI.Clutter.Objects.BoxLayout.BoxLayout' is arranging its children
    --   homogeneously, and 'P.False' otherwise
boxLayoutGetHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> m Bool
boxLayoutGetHomogeneous 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr BoxLayout -> IO CInt
clutter_box_layout_get_homogeneous Ptr BoxLayout
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 BoxLayoutGetHomogeneousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutGetHomogeneousMethodInfo a signature where
    overloadedMethod = boxLayoutGetHomogeneous

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


#endif

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

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

-- | Retrieves the orientation of the /@layout@/.
-- 
-- /Since: 1.12/
boxLayoutGetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m Clutter.Enums.Orientation
    -- ^ __Returns:__ the orientation of the layout
boxLayoutGetOrientation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> m Orientation
boxLayoutGetOrientation a
layout = IO Orientation -> m Orientation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Orientation -> m Orientation)
-> IO Orientation -> m Orientation
forall a b. (a -> b) -> a -> b
$ do
    Ptr BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CUInt
result <- Ptr BoxLayout -> IO CUInt
clutter_box_layout_get_orientation Ptr BoxLayout
layout'
    let result' :: Orientation
result' = (Int -> Orientation
forall a. Enum a => Int -> a
toEnum (Int -> Orientation) -> (CUInt -> Int) -> CUInt -> Orientation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Orientation -> IO Orientation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
result'

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

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


#endif

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

-- | Retrieves the value set using 'GI.Clutter.Objects.BoxLayout.boxLayoutSetPackStart'
-- 
-- /Since: 1.2/
boxLayoutGetPackStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the t'GI.Clutter.Objects.BoxLayout.BoxLayout' should pack children
    --  at the beginning of the layout, and 'P.False' otherwise
boxLayoutGetPackStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> m Bool
boxLayoutGetPackStart 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr BoxLayout -> IO CInt
clutter_box_layout_get_pack_start Ptr BoxLayout
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 BoxLayoutGetPackStartMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutGetPackStartMethodInfo a signature where
    overloadedMethod = boxLayoutGetPackStart

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


#endif

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

-- | Retrieves the spacing set using 'GI.Clutter.Objects.BoxLayout.boxLayoutSetSpacing'
-- 
-- /Since: 1.2/
boxLayoutGetSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m Word32
    -- ^ __Returns:__ the spacing between children of the t'GI.Clutter.Objects.BoxLayout.BoxLayout'
boxLayoutGetSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> m Word32
boxLayoutGetSpacing 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Word32
result <- Ptr BoxLayout -> IO Word32
clutter_box_layout_get_spacing Ptr BoxLayout
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 BoxLayoutGetSpacingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutGetSpacingMethodInfo a signature where
    overloadedMethod = boxLayoutGetSpacing

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


#endif

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

{-# DEPRECATED boxLayoutGetUseAnimations ["(Since version 1.12)"] #-}
-- | Retrieves whether /@layout@/ should animate changes in the layout properties.
-- 
-- /Since: 1.2/
boxLayoutGetUseAnimations ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the animations should be used, 'P.False' otherwise
boxLayoutGetUseAnimations :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> m Bool
boxLayoutGetUseAnimations 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr BoxLayout -> IO CInt
clutter_box_layout_get_use_animations Ptr BoxLayout
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 BoxLayoutGetUseAnimationsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutGetUseAnimationsMethodInfo a signature where
    overloadedMethod = boxLayoutGetUseAnimations

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


#endif

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

{-# DEPRECATED boxLayoutGetVertical ["(Since version 1.12)","Use 'GI.Clutter.Objects.BoxLayout.boxLayoutGetOrientation' instead"] #-}
-- | Retrieves the orientation of the /@layout@/ as set using the
-- 'GI.Clutter.Objects.BoxLayout.boxLayoutSetVertical' function
-- 
-- /Since: 1.2/
boxLayoutGetVertical ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the t'GI.Clutter.Objects.BoxLayout.BoxLayout' is arranging its children
    --   vertically, and 'P.False' otherwise
boxLayoutGetVertical :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> m Bool
boxLayoutGetVertical 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr BoxLayout -> IO CInt
clutter_box_layout_get_vertical Ptr BoxLayout
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 BoxLayoutGetVerticalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutGetVerticalMethodInfo a signature where
    overloadedMethod = boxLayoutGetVertical

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


#endif

-- method BoxLayout::pack
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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 = "expand"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether the @actor should expand"
--                 , 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 the @actor should fill horizontally"
--                 , 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 the @actor should fill vertically"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_align"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxAlignment" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the 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 = "BoxAlignment" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the 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_box_layout_pack" clutter_box_layout_pack :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CInt ->                                 -- expand : TBasicType TBoolean
    CInt ->                                 -- x_fill : TBasicType TBoolean
    CInt ->                                 -- y_fill : TBasicType TBoolean
    CUInt ->                                -- x_align : TInterface (Name {namespace = "Clutter", name = "BoxAlignment"})
    CUInt ->                                -- y_align : TInterface (Name {namespace = "Clutter", name = "BoxAlignment"})
    IO ()

{-# DEPRECATED boxLayoutPack ["(Since version 1.12)","t'GI.Clutter.Objects.BoxLayout.BoxLayout' honours t'GI.Clutter.Objects.Actor.Actor'\\'s","  align and expand properties. The preferred way is adding","  the /@actor@/ with 'GI.Clutter.Objects.Actor.actorAddChild' and setting","  [Actor:xAlign](\"GI.Clutter.Objects.Actor#g:attr:xAlign\"), [Actor:yAlign](\"GI.Clutter.Objects.Actor#g:attr:yAlign\"),","  [Actor:xExpand](\"GI.Clutter.Objects.Actor#g:attr:xExpand\") and [Actor:yExpand](\"GI.Clutter.Objects.Actor#g:attr:yExpand\")"] #-}
-- | Packs /@actor@/ inside the t'GI.Clutter.Interfaces.Container.Container' associated to /@layout@/
-- and sets the layout properties
-- 
-- /Since: 1.2/
boxLayoutPack ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor'
    -> Bool
    -- ^ /@expand@/: whether the /@actor@/ should expand
    -> Bool
    -- ^ /@xFill@/: whether the /@actor@/ should fill horizontally
    -> Bool
    -- ^ /@yFill@/: whether the /@actor@/ should fill vertically
    -> Clutter.Enums.BoxAlignment
    -- ^ /@xAlign@/: the horizontal alignment policy for /@actor@/
    -> Clutter.Enums.BoxAlignment
    -- ^ /@yAlign@/: the vertical alignment policy for /@actor@/
    -> m ()
boxLayoutPack :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBoxLayout a, IsActor b) =>
a
-> b
-> Bool
-> Bool
-> Bool
-> BoxAlignment
-> BoxAlignment
-> m ()
boxLayoutPack a
layout b
actor Bool
expand Bool
xFill Bool
yFill BoxAlignment
xAlign BoxAlignment
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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
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 expand' :: CInt
expand' = (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
expand
    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
    let xAlign' :: CUInt
xAlign' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (BoxAlignment -> Int) -> BoxAlignment -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BoxAlignment -> Int
forall a. Enum a => a -> Int
fromEnum) BoxAlignment
xAlign
    let yAlign' :: CUInt
yAlign' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (BoxAlignment -> Int) -> BoxAlignment -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BoxAlignment -> Int
forall a. Enum a => a -> Int
fromEnum) BoxAlignment
yAlign
    Ptr BoxLayout
-> Ptr Actor -> CInt -> CInt -> CInt -> CUInt -> CUInt -> IO ()
clutter_box_layout_pack Ptr BoxLayout
layout' Ptr Actor
actor' CInt
expand' CInt
xFill' CInt
yFill' 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 BoxLayoutPackMethodInfo
instance (signature ~ (b -> Bool -> Bool -> Bool -> Clutter.Enums.BoxAlignment -> Clutter.Enums.BoxAlignment -> m ()), MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod BoxLayoutPackMethodInfo a signature where
    overloadedMethod = boxLayoutPack

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


#endif

-- method BoxLayout::set_alignment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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 = "BoxAlignment" }
--           , 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 = "BoxAlignment" }
--           , 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_box_layout_set_alignment" clutter_box_layout_set_alignment :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CUInt ->                                -- x_align : TInterface (Name {namespace = "Clutter", name = "BoxAlignment"})
    CUInt ->                                -- y_align : TInterface (Name {namespace = "Clutter", name = "BoxAlignment"})
    IO ()

{-# DEPRECATED boxLayoutSetAlignment ["(Since version 1.12)","t'GI.Clutter.Objects.BoxLayout.BoxLayout' will honour t'GI.Clutter.Objects.Actor.Actor'\\'s","  [Actor:xAlign](\"GI.Clutter.Objects.Actor#g:attr:xAlign\") and [Actor:yAlign](\"GI.Clutter.Objects.Actor#g:attr:yAlign\") properies"] #-}
-- | Sets the horizontal and vertical alignment policies for /@actor@/
-- inside /@layout@/
-- 
-- /Since: 1.2/
boxLayoutSetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> Clutter.Enums.BoxAlignment
    -- ^ /@xAlign@/: Horizontal alignment policy for /@actor@/
    -> Clutter.Enums.BoxAlignment
    -- ^ /@yAlign@/: Vertical alignment policy for /@actor@/
    -> m ()
boxLayoutSetAlignment :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBoxLayout a, IsActor b) =>
a -> b -> BoxAlignment -> BoxAlignment -> m ()
boxLayoutSetAlignment a
layout b
actor BoxAlignment
xAlign BoxAlignment
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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
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) -> (BoxAlignment -> Int) -> BoxAlignment -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BoxAlignment -> Int
forall a. Enum a => a -> Int
fromEnum) BoxAlignment
xAlign
    let yAlign' :: CUInt
yAlign' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (BoxAlignment -> Int) -> BoxAlignment -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BoxAlignment -> Int
forall a. Enum a => a -> Int
fromEnum) BoxAlignment
yAlign
    Ptr BoxLayout -> Ptr Actor -> CUInt -> CUInt -> IO ()
clutter_box_layout_set_alignment Ptr BoxLayout
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 BoxLayoutSetAlignmentMethodInfo
instance (signature ~ (b -> Clutter.Enums.BoxAlignment -> Clutter.Enums.BoxAlignment -> m ()), MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod BoxLayoutSetAlignmentMethodInfo a signature where
    overloadedMethod = boxLayoutSetAlignment

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


#endif

-- method BoxLayout::set_easing_duration
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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_box_layout_set_easing_duration" clutter_box_layout_set_easing_duration :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    Word32 ->                               -- msecs : TBasicType TUInt
    IO ()

{-# DEPRECATED boxLayoutSetEasingDuration ["(Since version 1.12)","The layout manager will honour the easing state","  of the children when allocating them."] #-}
-- | Sets the duration of the animations used by /@layout@/ when animating changes
-- in the layout properties.
-- 
-- /Since: 1.2/
boxLayoutSetEasingDuration ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> Word32
    -- ^ /@msecs@/: the duration of the animations, in milliseconds
    -> m ()
boxLayoutSetEasingDuration :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> Word32 -> m ()
boxLayoutSetEasingDuration 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr BoxLayout -> Word32 -> IO ()
clutter_box_layout_set_easing_duration Ptr BoxLayout
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 BoxLayoutSetEasingDurationMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutSetEasingDurationMethodInfo a signature where
    overloadedMethod = boxLayoutSetEasingDuration

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


#endif

-- method BoxLayout::set_easing_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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_box_layout_set_easing_mode" clutter_box_layout_set_easing_mode :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    CULong ->                               -- mode : TBasicType TULong
    IO ()

{-# DEPRECATED boxLayoutSetEasingMode ["(Since version 1.12)","The layout manager will honour the easing state","  of the children when allocating them."] #-}
-- | Sets the easing mode to be used by /@layout@/ when animating changes in layout
-- properties.
-- 
-- /Since: 1.2/
boxLayoutSetEasingMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> CULong
    -- ^ /@mode@/: an easing mode, either from t'GI.Clutter.Enums.AnimationMode' or a logical id
    --   from @/clutter_alpha_register_func()/@
    -> m ()
boxLayoutSetEasingMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> CULong -> m ()
boxLayoutSetEasingMode 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr BoxLayout -> CULong -> IO ()
clutter_box_layout_set_easing_mode Ptr BoxLayout
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 BoxLayoutSetEasingModeMethodInfo
instance (signature ~ (CULong -> m ()), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutSetEasingModeMethodInfo a signature where
    overloadedMethod = boxLayoutSetEasingMode

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


#endif

-- method BoxLayout::set_expand
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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 = "expand"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether @actor should expand"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_box_layout_set_expand" clutter_box_layout_set_expand :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CInt ->                                 -- expand : TBasicType TBoolean
    IO ()

{-# DEPRECATED boxLayoutSetExpand ["(Since version 1.12)","t'GI.Clutter.Objects.BoxLayout.BoxLayout' will honour t'GI.Clutter.Objects.Actor.Actor'\\'s","  [Actor:xExpand](\"GI.Clutter.Objects.Actor#g:attr:xExpand\") and [Actor:yExpand](\"GI.Clutter.Objects.Actor#g:attr:yExpand\") properies"] #-}
-- | Sets whether /@actor@/ should expand inside /@layout@/
-- 
-- /Since: 1.2/
boxLayoutSetExpand ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> b
    -- ^ /@actor@/: a t'GI.Clutter.Objects.Actor.Actor' child of /@layout@/
    -> Bool
    -- ^ /@expand@/: whether /@actor@/ should expand
    -> m ()
boxLayoutSetExpand :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBoxLayout a, IsActor b) =>
a -> b -> Bool -> m ()
boxLayoutSetExpand a
layout b
actor Bool
expand = 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
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 expand' :: CInt
expand' = (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
expand
    Ptr BoxLayout -> Ptr Actor -> CInt -> IO ()
clutter_box_layout_set_expand Ptr BoxLayout
layout' Ptr Actor
actor' CInt
expand'
    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 BoxLayoutSetExpandMethodInfo
instance (signature ~ (b -> Bool -> m ()), MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod BoxLayoutSetExpandMethodInfo a signature where
    overloadedMethod = boxLayoutSetExpand

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


#endif

-- method BoxLayout::set_fill
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , 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_box_layout_set_fill" clutter_box_layout_set_fill :: 
    Ptr BoxLayout ->                        -- layout : TInterface (Name {namespace = "Clutter", name = "BoxLayout"})
    Ptr Clutter.Actor.Actor ->              -- actor : TInterface (Name {namespace = "Clutter", name = "Actor"})
    CInt ->                                 -- x_fill : TBasicType TBoolean
    CInt ->                                 -- y_fill : TBasicType TBoolean
    IO ()

{-# DEPRECATED boxLayoutSetFill ["(Since version 1.12)","t'GI.Clutter.Objects.BoxLayout.BoxLayout' will honour t'GI.Clutter.Objects.Actor.Actor'\\'s","  [Actor:xAlign](\"GI.Clutter.Objects.Actor#g:attr:xAlign\") and [Actor:yAlign](\"GI.Clutter.Objects.Actor#g:attr:yAlign\") properies"] #-}
-- | Sets the horizontal and vertical fill policies for /@actor@/
-- inside /@layout@/
-- 
-- /Since: 1.2/
boxLayoutSetFill ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> 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 ()
boxLayoutSetFill :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBoxLayout a, IsActor b) =>
a -> b -> Bool -> Bool -> m ()
boxLayoutSetFill 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
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 BoxLayout -> Ptr Actor -> CInt -> CInt -> IO ()
clutter_box_layout_set_fill Ptr BoxLayout
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 BoxLayoutSetFillMethodInfo
instance (signature ~ (b -> Bool -> Bool -> m ()), MonadIO m, IsBoxLayout a, Clutter.Actor.IsActor b) => O.OverloadedMethod BoxLayoutSetFillMethodInfo a signature where
    overloadedMethod = boxLayoutSetFill

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


#endif

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

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

-- | Sets whether the size of /@layout@/ children should be
-- homogeneous
-- 
-- /Since: 1.4/
boxLayoutSetHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> Bool
    -- ^ /@homogeneous@/: 'P.True' if the layout should be homogeneous
    -> m ()
boxLayoutSetHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> Bool -> m ()
boxLayoutSetHomogeneous a
layout Bool
homogeneous = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let homogeneous' :: CInt
homogeneous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
homogeneous
    Ptr BoxLayout -> CInt -> IO ()
clutter_box_layout_set_homogeneous Ptr BoxLayout
layout' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxLayoutSetHomogeneousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutSetHomogeneousMethodInfo a signature where
    overloadedMethod = boxLayoutSetHomogeneous

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


#endif

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

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

-- | Sets the orientation of the t'GI.Clutter.Objects.BoxLayout.BoxLayout' layout manager.
-- 
-- /Since: 1.12/
boxLayoutSetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> Clutter.Enums.Orientation
    -- ^ /@orientation@/: the orientation of the t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> m ()
boxLayoutSetOrientation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> Orientation -> m ()
boxLayoutSetOrientation a
layout Orientation
orientation = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let orientation' :: CUInt
orientation' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Orientation -> Int) -> Orientation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Orientation -> Int
forall a. Enum a => a -> Int
fromEnum) Orientation
orientation
    Ptr BoxLayout -> CUInt -> IO ()
clutter_box_layout_set_orientation Ptr BoxLayout
layout' CUInt
orientation'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method BoxLayout::set_pack_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "BoxLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterBoxLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pack_start"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "%TRUE if the @layout should pack children at the\n  beginning of the layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Sets whether children of /@layout@/ should be layed out by appending
-- them or by prepending them
-- 
-- /Since: 1.2/
boxLayoutSetPackStart ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> Bool
    -- ^ /@packStart@/: 'P.True' if the /@layout@/ should pack children at the
    --   beginning of the layout
    -> m ()
boxLayoutSetPackStart :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> Bool -> m ()
boxLayoutSetPackStart a
layout Bool
packStart = 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let packStart' :: CInt
packStart' = (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
packStart
    Ptr BoxLayout -> CInt -> IO ()
clutter_box_layout_set_pack_start Ptr BoxLayout
layout' CInt
packStart'
    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 BoxLayoutSetPackStartMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutSetPackStartMethodInfo a signature where
    overloadedMethod = boxLayoutSetPackStart

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


#endif

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

-- | Sets the spacing between children of /@layout@/
-- 
-- /Since: 1.2/
boxLayoutSetSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> Word32
    -- ^ /@spacing@/: the spacing between children of the layout, in pixels
    -> m ()
boxLayoutSetSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> Word32 -> m ()
boxLayoutSetSpacing 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr BoxLayout -> Word32 -> IO ()
clutter_box_layout_set_spacing Ptr BoxLayout
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 BoxLayoutSetSpacingMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutSetSpacingMethodInfo a signature where
    overloadedMethod = boxLayoutSetSpacing

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


#endif

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

{-# DEPRECATED boxLayoutSetUseAnimations ["(Since version 1.12)","The layout manager will honour the easing state","  of the children when allocating them."] #-}
-- | Sets whether /@layout@/ should animate changes in the layout properties
-- 
-- The duration of the animations is controlled by
-- 'GI.Clutter.Objects.BoxLayout.boxLayoutSetEasingDuration'; the easing mode to be used
-- by the animations is controlled by 'GI.Clutter.Objects.BoxLayout.boxLayoutSetEasingMode'.
-- 
-- Enabling animations will override the easing state of each child
-- of the actor using /@layout@/, and will use the [BoxLayout:easingMode]("GI.Clutter.Objects.BoxLayout#g:attr:easingMode")
-- and [BoxLayout:easingDuration]("GI.Clutter.Objects.BoxLayout#g:attr:easingDuration") properties instead.
-- 
-- /Since: 1.2/
boxLayoutSetUseAnimations ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> Bool
    -- ^ /@animate@/: 'P.True' if the /@layout@/ should use animations
    -> m ()
boxLayoutSetUseAnimations :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> Bool -> m ()
boxLayoutSetUseAnimations 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
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 BoxLayout -> CInt -> IO ()
clutter_box_layout_set_use_animations Ptr BoxLayout
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 BoxLayoutSetUseAnimationsMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutSetUseAnimationsMethodInfo a signature where
    overloadedMethod = boxLayoutSetUseAnimations

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


#endif

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

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

{-# DEPRECATED boxLayoutSetVertical ["(Since version 1.12)","Use 'GI.Clutter.Objects.BoxLayout.boxLayoutSetOrientation' instead."] #-}
-- | Sets whether /@layout@/ should arrange its children vertically alongside
-- the Y axis, instead of horizontally alongside the X axis
-- 
-- /Since: 1.2/
boxLayoutSetVertical ::
    (B.CallStack.HasCallStack, MonadIO m, IsBoxLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.BoxLayout.BoxLayout'
    -> Bool
    -- ^ /@vertical@/: 'P.True' if the layout should be vertical
    -> m ()
boxLayoutSetVertical :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBoxLayout a) =>
a -> Bool -> m ()
boxLayoutSetVertical a
layout Bool
vertical = 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 BoxLayout
layout' <- a -> IO (Ptr BoxLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let vertical' :: CInt
vertical' = (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
vertical
    Ptr BoxLayout -> CInt -> IO ()
clutter_box_layout_set_vertical Ptr BoxLayout
layout' CInt
vertical'
    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 BoxLayoutSetVerticalMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsBoxLayout a) => O.OverloadedMethod BoxLayoutSetVerticalMethodInfo a signature where
    overloadedMethod = boxLayoutSetVertical

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


#endif