{-# 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.FlowLayout.FlowLayout' 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.FlowLayout
    ( 

-- * Exported types
    FlowLayout(..)                          ,
    IsFlowLayout                            ,
    toFlowLayout                            ,


 -- * 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"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAnimationProgress]("GI.Clutter.Objects.LayoutManager#g:method:getAnimationProgress"), [getChildMeta]("GI.Clutter.Objects.LayoutManager#g:method:getChildMeta"), [getColumnSpacing]("GI.Clutter.Objects.FlowLayout#g:method:getColumnSpacing"), [getColumnWidth]("GI.Clutter.Objects.FlowLayout#g:method:getColumnWidth"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getHomogeneous]("GI.Clutter.Objects.FlowLayout#g:method:getHomogeneous"), [getOrientation]("GI.Clutter.Objects.FlowLayout#g:method:getOrientation"), [getPreferredHeight]("GI.Clutter.Objects.LayoutManager#g:method:getPreferredHeight"), [getPreferredWidth]("GI.Clutter.Objects.LayoutManager#g:method:getPreferredWidth"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRowHeight]("GI.Clutter.Objects.FlowLayout#g:method:getRowHeight"), [getRowSpacing]("GI.Clutter.Objects.FlowLayout#g:method:getRowSpacing"), [getSnapToGrid]("GI.Clutter.Objects.FlowLayout#g:method:getSnapToGrid").
-- 
-- ==== Setters
-- [setColumnSpacing]("GI.Clutter.Objects.FlowLayout#g:method:setColumnSpacing"), [setColumnWidth]("GI.Clutter.Objects.FlowLayout#g:method:setColumnWidth"), [setContainer]("GI.Clutter.Objects.LayoutManager#g:method:setContainer"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setHomogeneous]("GI.Clutter.Objects.FlowLayout#g:method:setHomogeneous"), [setOrientation]("GI.Clutter.Objects.FlowLayout#g:method:setOrientation"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRowHeight]("GI.Clutter.Objects.FlowLayout#g:method:setRowHeight"), [setRowSpacing]("GI.Clutter.Objects.FlowLayout#g:method:setRowSpacing"), [setSnapToGrid]("GI.Clutter.Objects.FlowLayout#g:method:setSnapToGrid").

#if defined(ENABLE_OVERLOADING)
    ResolveFlowLayoutMethod                 ,
#endif

-- ** getColumnSpacing #method:getColumnSpacing#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutGetColumnSpacingMethodInfo    ,
#endif
    flowLayoutGetColumnSpacing              ,


-- ** getColumnWidth #method:getColumnWidth#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutGetColumnWidthMethodInfo      ,
#endif
    flowLayoutGetColumnWidth                ,


-- ** getHomogeneous #method:getHomogeneous#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutGetHomogeneousMethodInfo      ,
#endif
    flowLayoutGetHomogeneous                ,


-- ** getOrientation #method:getOrientation#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutGetOrientationMethodInfo      ,
#endif
    flowLayoutGetOrientation                ,


-- ** getRowHeight #method:getRowHeight#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutGetRowHeightMethodInfo        ,
#endif
    flowLayoutGetRowHeight                  ,


-- ** getRowSpacing #method:getRowSpacing#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutGetRowSpacingMethodInfo       ,
#endif
    flowLayoutGetRowSpacing                 ,


-- ** getSnapToGrid #method:getSnapToGrid#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutGetSnapToGridMethodInfo       ,
#endif
    flowLayoutGetSnapToGrid                 ,


-- ** new #method:new#

    flowLayoutNew                           ,


-- ** setColumnSpacing #method:setColumnSpacing#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutSetColumnSpacingMethodInfo    ,
#endif
    flowLayoutSetColumnSpacing              ,


-- ** setColumnWidth #method:setColumnWidth#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutSetColumnWidthMethodInfo      ,
#endif
    flowLayoutSetColumnWidth                ,


-- ** setHomogeneous #method:setHomogeneous#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutSetHomogeneousMethodInfo      ,
#endif
    flowLayoutSetHomogeneous                ,


-- ** setOrientation #method:setOrientation#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutSetOrientationMethodInfo      ,
#endif
    flowLayoutSetOrientation                ,


-- ** setRowHeight #method:setRowHeight#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutSetRowHeightMethodInfo        ,
#endif
    flowLayoutSetRowHeight                  ,


-- ** setRowSpacing #method:setRowSpacing#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutSetRowSpacingMethodInfo       ,
#endif
    flowLayoutSetRowSpacing                 ,


-- ** setSnapToGrid #method:setSnapToGrid#

#if defined(ENABLE_OVERLOADING)
    FlowLayoutSetSnapToGridMethodInfo       ,
#endif
    flowLayoutSetSnapToGrid                 ,




 -- * Properties


-- ** columnSpacing #attr:columnSpacing#
-- | The spacing between columns, in pixels; the value of this
-- property is honoured by horizontal non-overflowing layouts
-- and by vertical overflowing layouts
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutColumnSpacingPropertyInfo     ,
#endif
    constructFlowLayoutColumnSpacing        ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutColumnSpacing                 ,
#endif
    getFlowLayoutColumnSpacing              ,
    setFlowLayoutColumnSpacing              ,


-- ** homogeneous #attr:homogeneous#
-- | Whether each child inside the t'GI.Clutter.Objects.FlowLayout.FlowLayout' should receive
-- the same allocation
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutHomogeneousPropertyInfo       ,
#endif
    constructFlowLayoutHomogeneous          ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutHomogeneous                   ,
#endif
    getFlowLayoutHomogeneous                ,
    setFlowLayoutHomogeneous                ,


-- ** maxColumnWidth #attr:maxColumnWidth#
-- | Maximum width for each column in the layout, in pixels. If
-- set to -1 the width will be the maximum child width
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutMaxColumnWidthPropertyInfo    ,
#endif
    constructFlowLayoutMaxColumnWidth       ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutMaxColumnWidth                ,
#endif
    getFlowLayoutMaxColumnWidth             ,
    setFlowLayoutMaxColumnWidth             ,


-- ** maxRowHeight #attr:maxRowHeight#
-- | Maximum height for each row in the layout, in pixels. If
-- set to -1 the width will be the maximum child height
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutMaxRowHeightPropertyInfo      ,
#endif
    constructFlowLayoutMaxRowHeight         ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutMaxRowHeight                  ,
#endif
    getFlowLayoutMaxRowHeight               ,
    setFlowLayoutMaxRowHeight               ,


-- ** minColumnWidth #attr:minColumnWidth#
-- | Minimum width for each column in the layout, in pixels
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutMinColumnWidthPropertyInfo    ,
#endif
    constructFlowLayoutMinColumnWidth       ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutMinColumnWidth                ,
#endif
    getFlowLayoutMinColumnWidth             ,
    setFlowLayoutMinColumnWidth             ,


-- ** minRowHeight #attr:minRowHeight#
-- | Minimum height for each row in the layout, in pixels
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutMinRowHeightPropertyInfo      ,
#endif
    constructFlowLayoutMinRowHeight         ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutMinRowHeight                  ,
#endif
    getFlowLayoutMinRowHeight               ,
    setFlowLayoutMinRowHeight               ,


-- ** orientation #attr:orientation#
-- | The orientation of the t'GI.Clutter.Objects.FlowLayout.FlowLayout'. The children
-- of the layout will be layed out following the orientation.
-- 
-- This property also controls the overflowing directions
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutOrientationPropertyInfo       ,
#endif
    constructFlowLayoutOrientation          ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutOrientation                   ,
#endif
    getFlowLayoutOrientation                ,
    setFlowLayoutOrientation                ,


-- ** rowSpacing #attr:rowSpacing#
-- | The spacing between rows, in pixels; the value of this
-- property is honoured by vertical non-overflowing layouts and
-- by horizontal overflowing layouts
-- 
-- /Since: 1.2/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutRowSpacingPropertyInfo        ,
#endif
    constructFlowLayoutRowSpacing           ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutRowSpacing                    ,
#endif
    getFlowLayoutRowSpacing                 ,
    setFlowLayoutRowSpacing                 ,


-- ** snapToGrid #attr:snapToGrid#
-- | Whether the t'GI.Clutter.Objects.FlowLayout.FlowLayout' should arrange its children
-- on a grid
-- 
-- /Since: 1.16/

#if defined(ENABLE_OVERLOADING)
    FlowLayoutSnapToGridPropertyInfo        ,
#endif
    constructFlowLayoutSnapToGrid           ,
#if defined(ENABLE_OVERLOADING)
    flowLayoutSnapToGrid                    ,
#endif
    getFlowLayoutSnapToGrid                 ,
    setFlowLayoutSnapToGrid                 ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

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

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

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

foreign import ccall "clutter_flow_layout_get_type"
    c_clutter_flow_layout_get_type :: IO B.Types.GType

instance B.Types.TypedObject FlowLayout where
    glibType :: IO GType
glibType = IO GType
c_clutter_flow_layout_get_type

instance B.Types.GObject FlowLayout

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveFlowLayoutMethod (t :: Symbol) (o :: *) :: * where
    ResolveFlowLayoutMethod "allocate" o = Clutter.LayoutManager.LayoutManagerAllocateMethodInfo
    ResolveFlowLayoutMethod "beginAnimation" o = Clutter.LayoutManager.LayoutManagerBeginAnimationMethodInfo
    ResolveFlowLayoutMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveFlowLayoutMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveFlowLayoutMethod "childGetProperty" o = Clutter.LayoutManager.LayoutManagerChildGetPropertyMethodInfo
    ResolveFlowLayoutMethod "childSetProperty" o = Clutter.LayoutManager.LayoutManagerChildSetPropertyMethodInfo
    ResolveFlowLayoutMethod "endAnimation" o = Clutter.LayoutManager.LayoutManagerEndAnimationMethodInfo
    ResolveFlowLayoutMethod "findChildProperty" o = Clutter.LayoutManager.LayoutManagerFindChildPropertyMethodInfo
    ResolveFlowLayoutMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveFlowLayoutMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveFlowLayoutMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveFlowLayoutMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveFlowLayoutMethod "layoutChanged" o = Clutter.LayoutManager.LayoutManagerLayoutChangedMethodInfo
    ResolveFlowLayoutMethod "listChildProperties" o = Clutter.LayoutManager.LayoutManagerListChildPropertiesMethodInfo
    ResolveFlowLayoutMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveFlowLayoutMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveFlowLayoutMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveFlowLayoutMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveFlowLayoutMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveFlowLayoutMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveFlowLayoutMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveFlowLayoutMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveFlowLayoutMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveFlowLayoutMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveFlowLayoutMethod "getAnimationProgress" o = Clutter.LayoutManager.LayoutManagerGetAnimationProgressMethodInfo
    ResolveFlowLayoutMethod "getChildMeta" o = Clutter.LayoutManager.LayoutManagerGetChildMetaMethodInfo
    ResolveFlowLayoutMethod "getColumnSpacing" o = FlowLayoutGetColumnSpacingMethodInfo
    ResolveFlowLayoutMethod "getColumnWidth" o = FlowLayoutGetColumnWidthMethodInfo
    ResolveFlowLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveFlowLayoutMethod "getHomogeneous" o = FlowLayoutGetHomogeneousMethodInfo
    ResolveFlowLayoutMethod "getOrientation" o = FlowLayoutGetOrientationMethodInfo
    ResolveFlowLayoutMethod "getPreferredHeight" o = Clutter.LayoutManager.LayoutManagerGetPreferredHeightMethodInfo
    ResolveFlowLayoutMethod "getPreferredWidth" o = Clutter.LayoutManager.LayoutManagerGetPreferredWidthMethodInfo
    ResolveFlowLayoutMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveFlowLayoutMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveFlowLayoutMethod "getRowHeight" o = FlowLayoutGetRowHeightMethodInfo
    ResolveFlowLayoutMethod "getRowSpacing" o = FlowLayoutGetRowSpacingMethodInfo
    ResolveFlowLayoutMethod "getSnapToGrid" o = FlowLayoutGetSnapToGridMethodInfo
    ResolveFlowLayoutMethod "setColumnSpacing" o = FlowLayoutSetColumnSpacingMethodInfo
    ResolveFlowLayoutMethod "setColumnWidth" o = FlowLayoutSetColumnWidthMethodInfo
    ResolveFlowLayoutMethod "setContainer" o = Clutter.LayoutManager.LayoutManagerSetContainerMethodInfo
    ResolveFlowLayoutMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveFlowLayoutMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveFlowLayoutMethod "setHomogeneous" o = FlowLayoutSetHomogeneousMethodInfo
    ResolveFlowLayoutMethod "setOrientation" o = FlowLayoutSetOrientationMethodInfo
    ResolveFlowLayoutMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveFlowLayoutMethod "setRowHeight" o = FlowLayoutSetRowHeightMethodInfo
    ResolveFlowLayoutMethod "setRowSpacing" o = FlowLayoutSetRowSpacingMethodInfo
    ResolveFlowLayoutMethod "setSnapToGrid" o = FlowLayoutSetSnapToGridMethodInfo
    ResolveFlowLayoutMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@column-spacing@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFlowLayoutColumnSpacing :: (IsFlowLayout o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructFlowLayoutColumnSpacing :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructFlowLayoutColumnSpacing Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"column-spacing" Float
val

#if defined(ENABLE_OVERLOADING)
data FlowLayoutColumnSpacingPropertyInfo
instance AttrInfo FlowLayoutColumnSpacingPropertyInfo where
    type AttrAllowedOps FlowLayoutColumnSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FlowLayoutColumnSpacingPropertyInfo = IsFlowLayout
    type AttrSetTypeConstraint FlowLayoutColumnSpacingPropertyInfo = (~) Float
    type AttrTransferTypeConstraint FlowLayoutColumnSpacingPropertyInfo = (~) Float
    type AttrTransferType FlowLayoutColumnSpacingPropertyInfo = Float
    type AttrGetType FlowLayoutColumnSpacingPropertyInfo = Float
    type AttrLabel FlowLayoutColumnSpacingPropertyInfo = "column-spacing"
    type AttrOrigin FlowLayoutColumnSpacingPropertyInfo = FlowLayout
    attrGet = getFlowLayoutColumnSpacing
    attrSet = setFlowLayoutColumnSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructFlowLayoutColumnSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.FlowLayout.columnSpacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-FlowLayout.html#g:attr:columnSpacing"
        })
#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' flowLayout #homogeneous
-- @
getFlowLayoutHomogeneous :: (MonadIO m, IsFlowLayout o) => o -> m Bool
getFlowLayoutHomogeneous :: forall (m :: * -> *) o. (MonadIO m, IsFlowLayout o) => o -> m Bool
getFlowLayoutHomogeneous o
obj = IO Bool -> m Bool
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' flowLayout [ #homogeneous 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlowLayoutHomogeneous :: (MonadIO m, IsFlowLayout o) => o -> Bool -> m ()
setFlowLayoutHomogeneous :: forall (m :: * -> *) o.
(MonadIO m, IsFlowLayout o) =>
o -> Bool -> m ()
setFlowLayoutHomogeneous o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> 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`.
constructFlowLayoutHomogeneous :: (IsFlowLayout o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructFlowLayoutHomogeneous :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructFlowLayoutHomogeneous Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"homogeneous" Bool
val

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

-- VVV Prop "max-column-width"
   -- Type: TBasicType TFloat
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@max-column-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' flowLayout [ #maxColumnWidth 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlowLayoutMaxColumnWidth :: (MonadIO m, IsFlowLayout o) => o -> Float -> m ()
setFlowLayoutMaxColumnWidth :: forall (m :: * -> *) o.
(MonadIO m, IsFlowLayout o) =>
o -> Float -> m ()
setFlowLayoutMaxColumnWidth o
obj Float
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Float -> IO ()
forall a. GObject a => a -> String -> Float -> IO ()
B.Properties.setObjectPropertyFloat o
obj String
"max-column-width" Float
val

-- | Construct a `GValueConstruct` with valid value for the “@max-column-width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFlowLayoutMaxColumnWidth :: (IsFlowLayout o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructFlowLayoutMaxColumnWidth :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructFlowLayoutMaxColumnWidth Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"max-column-width" Float
val

#if defined(ENABLE_OVERLOADING)
data FlowLayoutMaxColumnWidthPropertyInfo
instance AttrInfo FlowLayoutMaxColumnWidthPropertyInfo where
    type AttrAllowedOps FlowLayoutMaxColumnWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FlowLayoutMaxColumnWidthPropertyInfo = IsFlowLayout
    type AttrSetTypeConstraint FlowLayoutMaxColumnWidthPropertyInfo = (~) Float
    type AttrTransferTypeConstraint FlowLayoutMaxColumnWidthPropertyInfo = (~) Float
    type AttrTransferType FlowLayoutMaxColumnWidthPropertyInfo = Float
    type AttrGetType FlowLayoutMaxColumnWidthPropertyInfo = Float
    type AttrLabel FlowLayoutMaxColumnWidthPropertyInfo = "max-column-width"
    type AttrOrigin FlowLayoutMaxColumnWidthPropertyInfo = FlowLayout
    attrGet = getFlowLayoutMaxColumnWidth
    attrSet = setFlowLayoutMaxColumnWidth
    attrTransfer _ v = do
        return v
    attrConstruct = constructFlowLayoutMaxColumnWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.FlowLayout.maxColumnWidth"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-FlowLayout.html#g:attr:maxColumnWidth"
        })
#endif

-- VVV Prop "max-row-height"
   -- Type: TBasicType TFloat
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@max-row-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' flowLayout [ #maxRowHeight 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlowLayoutMaxRowHeight :: (MonadIO m, IsFlowLayout o) => o -> Float -> m ()
setFlowLayoutMaxRowHeight :: forall (m :: * -> *) o.
(MonadIO m, IsFlowLayout o) =>
o -> Float -> m ()
setFlowLayoutMaxRowHeight o
obj Float
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Float -> IO ()
forall a. GObject a => a -> String -> Float -> IO ()
B.Properties.setObjectPropertyFloat o
obj String
"max-row-height" Float
val

-- | Construct a `GValueConstruct` with valid value for the “@max-row-height@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFlowLayoutMaxRowHeight :: (IsFlowLayout o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructFlowLayoutMaxRowHeight :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructFlowLayoutMaxRowHeight Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"max-row-height" Float
val

#if defined(ENABLE_OVERLOADING)
data FlowLayoutMaxRowHeightPropertyInfo
instance AttrInfo FlowLayoutMaxRowHeightPropertyInfo where
    type AttrAllowedOps FlowLayoutMaxRowHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FlowLayoutMaxRowHeightPropertyInfo = IsFlowLayout
    type AttrSetTypeConstraint FlowLayoutMaxRowHeightPropertyInfo = (~) Float
    type AttrTransferTypeConstraint FlowLayoutMaxRowHeightPropertyInfo = (~) Float
    type AttrTransferType FlowLayoutMaxRowHeightPropertyInfo = Float
    type AttrGetType FlowLayoutMaxRowHeightPropertyInfo = Float
    type AttrLabel FlowLayoutMaxRowHeightPropertyInfo = "max-row-height"
    type AttrOrigin FlowLayoutMaxRowHeightPropertyInfo = FlowLayout
    attrGet = getFlowLayoutMaxRowHeight
    attrSet = setFlowLayoutMaxRowHeight
    attrTransfer _ v = do
        return v
    attrConstruct = constructFlowLayoutMaxRowHeight
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.FlowLayout.maxRowHeight"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-FlowLayout.html#g:attr:maxRowHeight"
        })
#endif

-- VVV Prop "min-column-width"
   -- Type: TBasicType TFloat
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@min-column-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' flowLayout [ #minColumnWidth 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlowLayoutMinColumnWidth :: (MonadIO m, IsFlowLayout o) => o -> Float -> m ()
setFlowLayoutMinColumnWidth :: forall (m :: * -> *) o.
(MonadIO m, IsFlowLayout o) =>
o -> Float -> m ()
setFlowLayoutMinColumnWidth o
obj Float
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Float -> IO ()
forall a. GObject a => a -> String -> Float -> IO ()
B.Properties.setObjectPropertyFloat o
obj String
"min-column-width" Float
val

-- | Construct a `GValueConstruct` with valid value for the “@min-column-width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFlowLayoutMinColumnWidth :: (IsFlowLayout o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructFlowLayoutMinColumnWidth :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructFlowLayoutMinColumnWidth Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"min-column-width" Float
val

#if defined(ENABLE_OVERLOADING)
data FlowLayoutMinColumnWidthPropertyInfo
instance AttrInfo FlowLayoutMinColumnWidthPropertyInfo where
    type AttrAllowedOps FlowLayoutMinColumnWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FlowLayoutMinColumnWidthPropertyInfo = IsFlowLayout
    type AttrSetTypeConstraint FlowLayoutMinColumnWidthPropertyInfo = (~) Float
    type AttrTransferTypeConstraint FlowLayoutMinColumnWidthPropertyInfo = (~) Float
    type AttrTransferType FlowLayoutMinColumnWidthPropertyInfo = Float
    type AttrGetType FlowLayoutMinColumnWidthPropertyInfo = Float
    type AttrLabel FlowLayoutMinColumnWidthPropertyInfo = "min-column-width"
    type AttrOrigin FlowLayoutMinColumnWidthPropertyInfo = FlowLayout
    attrGet = getFlowLayoutMinColumnWidth
    attrSet = setFlowLayoutMinColumnWidth
    attrTransfer _ v = do
        return v
    attrConstruct = constructFlowLayoutMinColumnWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.FlowLayout.minColumnWidth"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-FlowLayout.html#g:attr:minColumnWidth"
        })
#endif

-- VVV Prop "min-row-height"
   -- Type: TBasicType TFloat
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@min-row-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' flowLayout [ #minRowHeight 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlowLayoutMinRowHeight :: (MonadIO m, IsFlowLayout o) => o -> Float -> m ()
setFlowLayoutMinRowHeight :: forall (m :: * -> *) o.
(MonadIO m, IsFlowLayout o) =>
o -> Float -> m ()
setFlowLayoutMinRowHeight o
obj Float
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Float -> IO ()
forall a. GObject a => a -> String -> Float -> IO ()
B.Properties.setObjectPropertyFloat o
obj String
"min-row-height" Float
val

-- | Construct a `GValueConstruct` with valid value for the “@min-row-height@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFlowLayoutMinRowHeight :: (IsFlowLayout o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructFlowLayoutMinRowHeight :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructFlowLayoutMinRowHeight Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"min-row-height" Float
val

#if defined(ENABLE_OVERLOADING)
data FlowLayoutMinRowHeightPropertyInfo
instance AttrInfo FlowLayoutMinRowHeightPropertyInfo where
    type AttrAllowedOps FlowLayoutMinRowHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FlowLayoutMinRowHeightPropertyInfo = IsFlowLayout
    type AttrSetTypeConstraint FlowLayoutMinRowHeightPropertyInfo = (~) Float
    type AttrTransferTypeConstraint FlowLayoutMinRowHeightPropertyInfo = (~) Float
    type AttrTransferType FlowLayoutMinRowHeightPropertyInfo = Float
    type AttrGetType FlowLayoutMinRowHeightPropertyInfo = Float
    type AttrLabel FlowLayoutMinRowHeightPropertyInfo = "min-row-height"
    type AttrOrigin FlowLayoutMinRowHeightPropertyInfo = FlowLayout
    attrGet = getFlowLayoutMinRowHeight
    attrSet = setFlowLayoutMinRowHeight
    attrTransfer _ v = do
        return v
    attrConstruct = constructFlowLayoutMinRowHeight
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.FlowLayout.minRowHeight"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-FlowLayout.html#g:attr:minRowHeight"
        })
#endif

-- VVV Prop "orientation"
   -- Type: TInterface (Name {namespace = "Clutter", name = "FlowOrientation"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- 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' flowLayout #orientation
-- @
getFlowLayoutOrientation :: (MonadIO m, IsFlowLayout o) => o -> m Clutter.Enums.FlowOrientation
getFlowLayoutOrientation :: forall (m :: * -> *) o.
(MonadIO m, IsFlowLayout o) =>
o -> m FlowOrientation
getFlowLayoutOrientation o
obj = IO FlowOrientation -> m FlowOrientation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO FlowOrientation -> m FlowOrientation)
-> IO FlowOrientation -> m FlowOrientation
forall a b. (a -> b) -> a -> b
$ o -> String -> IO FlowOrientation
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' flowLayout [ #orientation 'Data.GI.Base.Attributes.:=' value ]
-- @
setFlowLayoutOrientation :: (MonadIO m, IsFlowLayout o) => o -> Clutter.Enums.FlowOrientation -> m ()
setFlowLayoutOrientation :: forall (m :: * -> *) o.
(MonadIO m, IsFlowLayout o) =>
o -> FlowOrientation -> m ()
setFlowLayoutOrientation o
obj FlowOrientation
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> FlowOrientation -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"orientation" FlowOrientation
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`.
constructFlowLayoutOrientation :: (IsFlowLayout o, MIO.MonadIO m) => Clutter.Enums.FlowOrientation -> m (GValueConstruct o)
constructFlowLayoutOrientation :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
FlowOrientation -> m (GValueConstruct o)
constructFlowLayoutOrientation FlowOrientation
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> FlowOrientation -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"orientation" FlowOrientation
val

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

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@row-spacing@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFlowLayoutRowSpacing :: (IsFlowLayout o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructFlowLayoutRowSpacing :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructFlowLayoutRowSpacing Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"row-spacing" Float
val

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

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@snap-to-grid@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFlowLayoutSnapToGrid :: (IsFlowLayout o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructFlowLayoutSnapToGrid :: forall o (m :: * -> *).
(IsFlowLayout o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructFlowLayoutSnapToGrid Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"snap-to-grid" Bool
val

#if defined(ENABLE_OVERLOADING)
data FlowLayoutSnapToGridPropertyInfo
instance AttrInfo FlowLayoutSnapToGridPropertyInfo where
    type AttrAllowedOps FlowLayoutSnapToGridPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FlowLayoutSnapToGridPropertyInfo = IsFlowLayout
    type AttrSetTypeConstraint FlowLayoutSnapToGridPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint FlowLayoutSnapToGridPropertyInfo = (~) Bool
    type AttrTransferType FlowLayoutSnapToGridPropertyInfo = Bool
    type AttrGetType FlowLayoutSnapToGridPropertyInfo = Bool
    type AttrLabel FlowLayoutSnapToGridPropertyInfo = "snap-to-grid"
    type AttrOrigin FlowLayoutSnapToGridPropertyInfo = FlowLayout
    attrGet = getFlowLayoutSnapToGrid
    attrSet = setFlowLayoutSnapToGrid
    attrTransfer _ v = do
        return v
    attrConstruct = constructFlowLayoutSnapToGrid
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.FlowLayout.snapToGrid"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.2/docs/GI-Clutter-Objects-FlowLayout.html#g:attr:snapToGrid"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FlowLayout
type instance O.AttributeList FlowLayout = FlowLayoutAttributeList
type FlowLayoutAttributeList = ('[ '("columnSpacing", FlowLayoutColumnSpacingPropertyInfo), '("homogeneous", FlowLayoutHomogeneousPropertyInfo), '("maxColumnWidth", FlowLayoutMaxColumnWidthPropertyInfo), '("maxRowHeight", FlowLayoutMaxRowHeightPropertyInfo), '("minColumnWidth", FlowLayoutMinColumnWidthPropertyInfo), '("minRowHeight", FlowLayoutMinRowHeightPropertyInfo), '("orientation", FlowLayoutOrientationPropertyInfo), '("rowSpacing", FlowLayoutRowSpacingPropertyInfo), '("snapToGrid", FlowLayoutSnapToGridPropertyInfo)] :: [(Symbol, *)])
#endif

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

flowLayoutHomogeneous :: AttrLabelProxy "homogeneous"
flowLayoutHomogeneous = AttrLabelProxy

flowLayoutMaxColumnWidth :: AttrLabelProxy "maxColumnWidth"
flowLayoutMaxColumnWidth = AttrLabelProxy

flowLayoutMaxRowHeight :: AttrLabelProxy "maxRowHeight"
flowLayoutMaxRowHeight = AttrLabelProxy

flowLayoutMinColumnWidth :: AttrLabelProxy "minColumnWidth"
flowLayoutMinColumnWidth = AttrLabelProxy

flowLayoutMinRowHeight :: AttrLabelProxy "minRowHeight"
flowLayoutMinRowHeight = AttrLabelProxy

flowLayoutOrientation :: AttrLabelProxy "orientation"
flowLayoutOrientation = AttrLabelProxy

flowLayoutRowSpacing :: AttrLabelProxy "rowSpacing"
flowLayoutRowSpacing = AttrLabelProxy

flowLayoutSnapToGrid :: AttrLabelProxy "snapToGrid"
flowLayoutSnapToGrid = AttrLabelProxy

#endif

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

#endif

-- method FlowLayout::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "orientation"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "FlowOrientation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the orientation of the flow layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "FlowLayout" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_flow_layout_new" clutter_flow_layout_new :: 
    CUInt ->                                -- orientation : TInterface (Name {namespace = "Clutter", name = "FlowOrientation"})
    IO (Ptr FlowLayout)

-- | Creates a new t'GI.Clutter.Objects.FlowLayout.FlowLayout' with the given /@orientation@/
-- 
-- /Since: 1.2/
flowLayoutNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Clutter.Enums.FlowOrientation
    -- ^ /@orientation@/: the orientation of the flow layout
    -> m FlowLayout
    -- ^ __Returns:__ the newly created t'GI.Clutter.Objects.FlowLayout.FlowLayout'
flowLayoutNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FlowOrientation -> m FlowLayout
flowLayoutNew FlowOrientation
orientation = IO FlowLayout -> m FlowLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FlowLayout -> m FlowLayout) -> IO FlowLayout -> m FlowLayout
forall a b. (a -> b) -> a -> b
$ do
    let orientation' :: CUInt
orientation' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (FlowOrientation -> Int) -> FlowOrientation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowOrientation -> Int
forall a. Enum a => a -> Int
fromEnum) FlowOrientation
orientation
    Ptr FlowLayout
result <- CUInt -> IO (Ptr FlowLayout)
clutter_flow_layout_new CUInt
orientation'
    Text -> Ptr FlowLayout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"flowLayoutNew" Ptr FlowLayout
result
    FlowLayout
result' <- ((ManagedPtr FlowLayout -> FlowLayout)
-> Ptr FlowLayout -> IO FlowLayout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FlowLayout -> FlowLayout
FlowLayout) Ptr FlowLayout
result
    FlowLayout -> IO FlowLayout
forall (m :: * -> *) a. Monad m => a -> m a
return FlowLayout
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "clutter_flow_layout_get_column_spacing" clutter_flow_layout_get_column_spacing :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    IO CFloat

-- | Retrieves the spacing between columns
-- 
-- /Since: 1.2/
flowLayoutGetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> m Float
    -- ^ __Returns:__ the spacing between columns of the t'GI.Clutter.Objects.FlowLayout.FlowLayout',
    --   in pixels
flowLayoutGetColumnSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> m Float
flowLayoutGetColumnSpacing a
layout = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CFloat
result <- Ptr FlowLayout -> IO CFloat
clutter_flow_layout_get_column_spacing Ptr FlowLayout
layout'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data FlowLayoutGetColumnSpacingMethodInfo
instance (signature ~ (m Float), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutGetColumnSpacingMethodInfo a signature where
    overloadedMethod = flowLayoutGetColumnSpacing

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


#endif

-- method FlowLayout::get_column_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min_width"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the minimum column width, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "max_width"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the maximum column width, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_flow_layout_get_column_width" clutter_flow_layout_get_column_width :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    Ptr CFloat ->                           -- min_width : TBasicType TFloat
    Ptr CFloat ->                           -- max_width : TBasicType TFloat
    IO ()

-- | Retrieves the minimum and maximum column widths
-- 
-- /Since: 1.2/
flowLayoutGetColumnWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> m ((Float, Float))
flowLayoutGetColumnWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> m (Float, Float)
flowLayoutGetColumnWidth a
layout = IO (Float, Float) -> m (Float, Float)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float) -> m (Float, Float))
-> IO (Float, Float) -> m (Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr CFloat
minWidth <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
maxWidth <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr FlowLayout -> Ptr CFloat -> Ptr CFloat -> IO ()
clutter_flow_layout_get_column_width Ptr FlowLayout
layout' Ptr CFloat
minWidth Ptr CFloat
maxWidth
    CFloat
minWidth' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
minWidth
    let minWidth'' :: Float
minWidth'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
minWidth'
    CFloat
maxWidth' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
maxWidth
    let maxWidth'' :: Float
maxWidth'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
maxWidth'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
minWidth
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
maxWidth
    (Float, Float) -> IO (Float, Float)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
minWidth'', Float
maxWidth'')

#if defined(ENABLE_OVERLOADING)
data FlowLayoutGetColumnWidthMethodInfo
instance (signature ~ (m ((Float, Float))), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutGetColumnWidthMethodInfo a signature where
    overloadedMethod = flowLayoutGetColumnWidth

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


#endif

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

-- | Retrieves whether the /@layout@/ is homogeneous
-- 
-- /Since: 1.2/
flowLayoutGetHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the t'GI.Clutter.Objects.FlowLayout.FlowLayout' is homogeneous
flowLayoutGetHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> m Bool
flowLayoutGetHomogeneous a
layout = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr FlowLayout -> IO CInt
clutter_flow_layout_get_homogeneous Ptr FlowLayout
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 (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FlowLayoutGetHomogeneousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutGetHomogeneousMethodInfo a signature where
    overloadedMethod = flowLayoutGetHomogeneous

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


#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data FlowLayoutGetOrientationMethodInfo
instance (signature ~ (m Clutter.Enums.FlowOrientation), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutGetOrientationMethodInfo a signature where
    overloadedMethod = flowLayoutGetOrientation

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


#endif

-- method FlowLayout::get_row_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min_height"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the minimum row height, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "max_height"
--           , argType = TBasicType TFloat
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the maximum row height, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_flow_layout_get_row_height" clutter_flow_layout_get_row_height :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    Ptr CFloat ->                           -- min_height : TBasicType TFloat
    Ptr CFloat ->                           -- max_height : TBasicType TFloat
    IO ()

-- | Retrieves the minimum and maximum row heights
-- 
-- /Since: 1.2/
flowLayoutGetRowHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> m ((Float, Float))
flowLayoutGetRowHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> m (Float, Float)
flowLayoutGetRowHeight a
layout = IO (Float, Float) -> m (Float, Float)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Float, Float) -> m (Float, Float))
-> IO (Float, Float) -> m (Float, Float)
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr CFloat
minHeight <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr CFloat
maxHeight <- IO (Ptr CFloat)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CFloat)
    Ptr FlowLayout -> Ptr CFloat -> Ptr CFloat -> IO ()
clutter_flow_layout_get_row_height Ptr FlowLayout
layout' Ptr CFloat
minHeight Ptr CFloat
maxHeight
    CFloat
minHeight' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
minHeight
    let minHeight'' :: Float
minHeight'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
minHeight'
    CFloat
maxHeight' <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
maxHeight
    let maxHeight'' :: Float
maxHeight'' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
maxHeight'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
minHeight
    Ptr CFloat -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CFloat
maxHeight
    (Float, Float) -> IO (Float, Float)
forall (m :: * -> *) a. Monad m => a -> m a
return (Float
minHeight'', Float
maxHeight'')

#if defined(ENABLE_OVERLOADING)
data FlowLayoutGetRowHeightMethodInfo
instance (signature ~ (m ((Float, Float))), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutGetRowHeightMethodInfo a signature where
    overloadedMethod = flowLayoutGetRowHeight

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


#endif

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

foreign import ccall "clutter_flow_layout_get_row_spacing" clutter_flow_layout_get_row_spacing :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    IO CFloat

-- | Retrieves the spacing between rows
-- 
-- /Since: 1.2/
flowLayoutGetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> m Float
    -- ^ __Returns:__ the spacing between rows of the t'GI.Clutter.Objects.FlowLayout.FlowLayout',
    --   in pixels
flowLayoutGetRowSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> m Float
flowLayoutGetRowSpacing a
layout = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CFloat
result <- Ptr FlowLayout -> IO CFloat
clutter_flow_layout_get_row_spacing Ptr FlowLayout
layout'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data FlowLayoutGetRowSpacingMethodInfo
instance (signature ~ (m Float), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutGetRowSpacingMethodInfo a signature where
    overloadedMethod = flowLayoutGetRowSpacing

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


#endif

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

-- | Retrieves the value of t'GI.Clutter.Objects.FlowLayout.FlowLayout':@/snap-to-grid/@ property
-- 
-- /Since: 1.16/
flowLayoutGetSnapToGrid ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@layout@/ is placing its children on a grid
flowLayoutGetSnapToGrid :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> m Bool
flowLayoutGetSnapToGrid a
layout = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr FlowLayout -> IO CInt
clutter_flow_layout_get_snap_to_grid Ptr FlowLayout
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 (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FlowLayoutGetSnapToGridMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutGetSnapToGridMethodInfo a signature where
    overloadedMethod = flowLayoutGetSnapToGrid

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


#endif

-- method FlowLayout::set_column_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spacing"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the space between columns"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_flow_layout_set_column_spacing" clutter_flow_layout_set_column_spacing :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    CFloat ->                               -- spacing : TBasicType TFloat
    IO ()

-- | Sets the space between columns, in pixels
-- 
-- /Since: 1.2/
flowLayoutSetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> Float
    -- ^ /@spacing@/: the space between columns
    -> m ()
flowLayoutSetColumnSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> Float -> m ()
flowLayoutSetColumnSpacing a
layout Float
spacing = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let spacing' :: CFloat
spacing' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
spacing
    Ptr FlowLayout -> CFloat -> IO ()
clutter_flow_layout_set_column_spacing Ptr FlowLayout
layout' CFloat
spacing'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FlowLayoutSetColumnSpacingMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutSetColumnSpacingMethodInfo a signature where
    overloadedMethod = flowLayoutSetColumnSpacing

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


#endif

-- method FlowLayout::set_column_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min_width"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "minimum width of a column"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "max_width"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "maximum width of a column"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_flow_layout_set_column_width" clutter_flow_layout_set_column_width :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    CFloat ->                               -- min_width : TBasicType TFloat
    CFloat ->                               -- max_width : TBasicType TFloat
    IO ()

-- | Sets the minimum and maximum widths that a column can have
-- 
-- /Since: 1.2/
flowLayoutSetColumnWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> Float
    -- ^ /@minWidth@/: minimum width of a column
    -> Float
    -- ^ /@maxWidth@/: maximum width of a column
    -> m ()
flowLayoutSetColumnWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> Float -> Float -> m ()
flowLayoutSetColumnWidth a
layout Float
minWidth Float
maxWidth = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let minWidth' :: CFloat
minWidth' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
minWidth
    let maxWidth' :: CFloat
maxWidth' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
maxWidth
    Ptr FlowLayout -> CFloat -> CFloat -> IO ()
clutter_flow_layout_set_column_width Ptr FlowLayout
layout' CFloat
minWidth' CFloat
maxWidth'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FlowLayoutSetColumnWidthMethodInfo
instance (signature ~ (Float -> Float -> m ()), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutSetColumnWidthMethodInfo a signature where
    overloadedMethod = flowLayoutSetColumnWidth

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


#endif

-- method FlowLayout::set_homogeneous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , 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 "whether the layout should be homogeneous or not"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Sets whether the /@layout@/ should allocate the same space for
-- each child
-- 
-- /Since: 1.2/
flowLayoutSetHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> Bool
    -- ^ /@homogeneous@/: whether the layout should be homogeneous or not
    -> m ()
flowLayoutSetHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> Bool -> m ()
flowLayoutSetHomogeneous a
layout Bool
homogeneous = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
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 FlowLayout -> CInt -> IO ()
clutter_flow_layout_set_homogeneous Ptr FlowLayout
layout' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FlowLayoutSetHomogeneousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutSetHomogeneousMethodInfo a signature where
    overloadedMethod = flowLayoutSetHomogeneous

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


#endif

-- method FlowLayout::set_orientation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "orientation"
--           , argType =
--               TInterface
--                 Name { namespace = "Clutter" , name = "FlowOrientation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the orientation 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_flow_layout_set_orientation" clutter_flow_layout_set_orientation :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    CUInt ->                                -- orientation : TInterface (Name {namespace = "Clutter", name = "FlowOrientation"})
    IO ()

-- | Sets the orientation of the flow layout
-- 
-- The orientation controls the direction used to allocate
-- the children: either horizontally or vertically. The
-- orientation also controls the direction of the overflowing
-- 
-- /Since: 1.2/
flowLayoutSetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> Clutter.Enums.FlowOrientation
    -- ^ /@orientation@/: the orientation of the layout
    -> m ()
flowLayoutSetOrientation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> FlowOrientation -> m ()
flowLayoutSetOrientation a
layout FlowOrientation
orientation = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
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)
-> (FlowOrientation -> Int) -> FlowOrientation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlowOrientation -> Int
forall a. Enum a => a -> Int
fromEnum) FlowOrientation
orientation
    Ptr FlowLayout -> CUInt -> IO ()
clutter_flow_layout_set_orientation Ptr FlowLayout
layout' CUInt
orientation'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FlowLayoutSetOrientationMethodInfo
instance (signature ~ (Clutter.Enums.FlowOrientation -> m ()), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutSetOrientationMethodInfo a signature where
    overloadedMethod = flowLayoutSetOrientation

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


#endif

-- method FlowLayout::set_row_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "min_height"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the minimum height of a row"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "max_height"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the maximum height of a row"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_flow_layout_set_row_height" clutter_flow_layout_set_row_height :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    CFloat ->                               -- min_height : TBasicType TFloat
    CFloat ->                               -- max_height : TBasicType TFloat
    IO ()

-- | Sets the minimum and maximum heights that a row can have
-- 
-- /Since: 1.2/
flowLayoutSetRowHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> Float
    -- ^ /@minHeight@/: the minimum height of a row
    -> Float
    -- ^ /@maxHeight@/: the maximum height of a row
    -> m ()
flowLayoutSetRowHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> Float -> Float -> m ()
flowLayoutSetRowHeight a
layout Float
minHeight Float
maxHeight = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let minHeight' :: CFloat
minHeight' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
minHeight
    let maxHeight' :: CFloat
maxHeight' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
maxHeight
    Ptr FlowLayout -> CFloat -> CFloat -> IO ()
clutter_flow_layout_set_row_height Ptr FlowLayout
layout' CFloat
minHeight' CFloat
maxHeight'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FlowLayoutSetRowHeightMethodInfo
instance (signature ~ (Float -> Float -> m ()), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutSetRowHeightMethodInfo a signature where
    overloadedMethod = flowLayoutSetRowHeight

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


#endif

-- method FlowLayout::set_row_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spacing"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the space between rows"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "clutter_flow_layout_set_row_spacing" clutter_flow_layout_set_row_spacing :: 
    Ptr FlowLayout ->                       -- layout : TInterface (Name {namespace = "Clutter", name = "FlowLayout"})
    CFloat ->                               -- spacing : TBasicType TFloat
    IO ()

-- | Sets the spacing between rows, in pixels
-- 
-- /Since: 1.2/
flowLayoutSetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> Float
    -- ^ /@spacing@/: the space between rows
    -> m ()
flowLayoutSetRowSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> Float -> m ()
flowLayoutSetRowSpacing a
layout Float
spacing = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let spacing' :: CFloat
spacing' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
spacing
    Ptr FlowLayout -> CFloat -> IO ()
clutter_flow_layout_set_row_spacing Ptr FlowLayout
layout' CFloat
spacing'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FlowLayoutSetRowSpacingMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutSetRowSpacingMethodInfo a signature where
    overloadedMethod = flowLayoutSetRowSpacing

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


#endif

-- method FlowLayout::set_snap_to_grid
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Clutter" , name = "FlowLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #ClutterFlowLayout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "snap_to_grid"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE if @layout should place its children on a grid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Whether the /@layout@/ should place its children on a grid.
-- 
-- /Since: 1.16/
flowLayoutSetSnapToGrid ::
    (B.CallStack.HasCallStack, MonadIO m, IsFlowLayout a) =>
    a
    -- ^ /@layout@/: a t'GI.Clutter.Objects.FlowLayout.FlowLayout'
    -> Bool
    -- ^ /@snapToGrid@/: 'P.True' if /@layout@/ should place its children on a grid
    -> m ()
flowLayoutSetSnapToGrid :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFlowLayout a) =>
a -> Bool -> m ()
flowLayoutSetSnapToGrid a
layout Bool
snapToGrid = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FlowLayout
layout' <- a -> IO (Ptr FlowLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let snapToGrid' :: CInt
snapToGrid' = (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
snapToGrid
    Ptr FlowLayout -> CInt -> IO ()
clutter_flow_layout_set_snap_to_grid Ptr FlowLayout
layout' CInt
snapToGrid'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FlowLayoutSetSnapToGridMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFlowLayout a) => O.OverloadedMethod FlowLayoutSetSnapToGridMethodInfo a signature where
    overloadedMethod = flowLayoutSetSnapToGrid

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


#endif