{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The @GtkBox@ widget arranges child widgets into a single row or column.
-- 
-- <<https://docs.gtk.org/gtk4/box.png An example GtkBox>>
-- 
-- Whether it is a row or column depends on the value of its
-- t'GI.Gtk.Interfaces.Orientable.Orientable':@/orientation/@ property. Within the other
-- dimension, all children are allocated the same size. Of course, the
-- [Widget:halign]("GI.Gtk.Objects.Widget#g:attr:halign") and [Widget:valign]("GI.Gtk.Objects.Widget#g:attr:valign") properties
-- can be used on the children to influence their allocation.
-- 
-- Use repeated calls to 'GI.Gtk.Objects.Box.boxAppend' to pack widgets into a
-- @GtkBox@ from start to end. Use 'GI.Gtk.Objects.Box.boxRemove' to remove widgets
-- from the @GtkBox@. 'GI.Gtk.Objects.Box.boxInsertChildAfter' can be used to add
-- a child at a particular position.
-- 
-- Use 'GI.Gtk.Objects.Box.boxSetHomogeneous' to specify whether or not all children
-- of the @GtkBox@ are forced to get the same amount of space.
-- 
-- Use 'GI.Gtk.Objects.Box.boxSetSpacing' to determine how much space will be minimally
-- placed between all children in the @GtkBox@. Note that spacing is added
-- *between* the children.
-- 
-- Use 'GI.Gtk.Objects.Box.boxReorderChildAfter' to move a child to a different
-- place in the box.
-- 
-- = CSS nodes
-- 
-- @GtkBox@ uses a single CSS node with name box.
-- 
-- = Accessibility
-- 
-- @GtkBox@ uses the 'GI.Gtk.Enums.AccessibleRoleGroup' role.

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

module GI.Gtk.Objects.Box
    ( 

-- * Exported types
    Box(..)                                 ,
    IsBox                                   ,
    toBox                                   ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [append]("GI.Gtk.Objects.Box#g:method:append"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [insertChildAfter]("GI.Gtk.Objects.Box#g:method:insertChildAfter"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [prepend]("GI.Gtk.Objects.Box#g:method:prepend"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [remove]("GI.Gtk.Objects.Box#g:method:remove"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [reorderChildAfter]("GI.Gtk.Objects.Box#g:method:reorderChildAfter"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:updateNextAccessibleSibling"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleParent"), [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getAtContext]("GI.Gtk.Interfaces.Accessible#g:method:getAtContext"), [getBaselinePosition]("GI.Gtk.Objects.Box#g:method:getBaselinePosition"), [getBounds]("GI.Gtk.Interfaces.Accessible#g:method:getBounds"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getColor]("GI.Gtk.Objects.Widget#g:method:getColor"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstAccessibleChild]("GI.Gtk.Interfaces.Accessible#g:method:getFirstAccessibleChild"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getHomogeneous]("GI.Gtk.Objects.Box#g:method:getHomogeneous"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:getNextAccessibleSibling"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOrientation]("GI.Gtk.Interfaces.Orientable#g:method:getOrientation"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPlatformState]("GI.Gtk.Interfaces.Accessible#g:method:getPlatformState"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getSpacing]("GI.Gtk.Objects.Box#g:method:getSpacing"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:setAccessibleParent"), [setBaselinePosition]("GI.Gtk.Objects.Box#g:method:setBaselinePosition"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setHomogeneous]("GI.Gtk.Objects.Box#g:method:setHomogeneous"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOrientation]("GI.Gtk.Interfaces.Orientable#g:method:setOrientation"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setSpacing]("GI.Gtk.Objects.Box#g:method:setSpacing"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveBoxMethod                        ,
#endif

-- ** append #method:append#

#if defined(ENABLE_OVERLOADING)
    BoxAppendMethodInfo                     ,
#endif
    boxAppend                               ,


-- ** getBaselinePosition #method:getBaselinePosition#

#if defined(ENABLE_OVERLOADING)
    BoxGetBaselinePositionMethodInfo        ,
#endif
    boxGetBaselinePosition                  ,


-- ** getHomogeneous #method:getHomogeneous#

#if defined(ENABLE_OVERLOADING)
    BoxGetHomogeneousMethodInfo             ,
#endif
    boxGetHomogeneous                       ,


-- ** getSpacing #method:getSpacing#

#if defined(ENABLE_OVERLOADING)
    BoxGetSpacingMethodInfo                 ,
#endif
    boxGetSpacing                           ,


-- ** insertChildAfter #method:insertChildAfter#

#if defined(ENABLE_OVERLOADING)
    BoxInsertChildAfterMethodInfo           ,
#endif
    boxInsertChildAfter                     ,


-- ** new #method:new#

    boxNew                                  ,


-- ** prepend #method:prepend#

#if defined(ENABLE_OVERLOADING)
    BoxPrependMethodInfo                    ,
#endif
    boxPrepend                              ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    BoxRemoveMethodInfo                     ,
#endif
    boxRemove                               ,


-- ** reorderChildAfter #method:reorderChildAfter#

#if defined(ENABLE_OVERLOADING)
    BoxReorderChildAfterMethodInfo          ,
#endif
    boxReorderChildAfter                    ,


-- ** setBaselinePosition #method:setBaselinePosition#

#if defined(ENABLE_OVERLOADING)
    BoxSetBaselinePositionMethodInfo        ,
#endif
    boxSetBaselinePosition                  ,


-- ** setHomogeneous #method:setHomogeneous#

#if defined(ENABLE_OVERLOADING)
    BoxSetHomogeneousMethodInfo             ,
#endif
    boxSetHomogeneous                       ,


-- ** setSpacing #method:setSpacing#

#if defined(ENABLE_OVERLOADING)
    BoxSetSpacingMethodInfo                 ,
#endif
    boxSetSpacing                           ,




 -- * Properties


-- ** baselinePosition #attr:baselinePosition#
-- | The position of the baseline aligned widgets if extra space is available.

#if defined(ENABLE_OVERLOADING)
    BoxBaselinePositionPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxBaselinePosition                     ,
#endif
    constructBoxBaselinePosition            ,
    getBoxBaselinePosition                  ,
    setBoxBaselinePosition                  ,


-- ** homogeneous #attr:homogeneous#
-- | Whether the children should all be the same size.

#if defined(ENABLE_OVERLOADING)
    BoxHomogeneousPropertyInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxHomogeneous                          ,
#endif
    constructBoxHomogeneous                 ,
    getBoxHomogeneous                       ,
    setBoxHomogeneous                       ,


-- ** spacing #attr:spacing#
-- | The amount of space between children.

#if defined(ENABLE_OVERLOADING)
    BoxSpacingPropertyInfo                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    boxSpacing                              ,
#endif
    constructBoxSpacing                     ,
    getBoxSpacing                           ,
    setBoxSpacing                           ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_box_get_type"
    c_gtk_box_get_type :: IO B.Types.GType

instance B.Types.TypedObject Box where
    glibType :: IO GType
glibType = IO GType
c_gtk_box_get_type

instance B.Types.GObject Box

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

instance O.HasParentTypes Box
type instance O.ParentTypes Box = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget, Gtk.Orientable.Orientable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveBoxMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveBoxMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveBoxMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveBoxMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveBoxMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveBoxMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveBoxMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveBoxMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveBoxMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveBoxMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveBoxMethod "append" o = BoxAppendMethodInfo
    ResolveBoxMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBoxMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBoxMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveBoxMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveBoxMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveBoxMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveBoxMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveBoxMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveBoxMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveBoxMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveBoxMethod "disposeTemplate" o = Gtk.Widget.WidgetDisposeTemplateMethodInfo
    ResolveBoxMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveBoxMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveBoxMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBoxMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBoxMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBoxMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveBoxMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveBoxMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveBoxMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveBoxMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveBoxMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveBoxMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveBoxMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveBoxMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveBoxMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveBoxMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveBoxMethod "insertChildAfter" o = BoxInsertChildAfterMethodInfo
    ResolveBoxMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveBoxMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveBoxMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveBoxMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveBoxMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveBoxMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveBoxMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveBoxMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveBoxMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveBoxMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveBoxMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveBoxMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveBoxMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveBoxMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveBoxMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveBoxMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveBoxMethod "prepend" o = BoxPrependMethodInfo
    ResolveBoxMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveBoxMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveBoxMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveBoxMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveBoxMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBoxMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBoxMethod "remove" o = BoxRemoveMethodInfo
    ResolveBoxMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveBoxMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveBoxMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveBoxMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveBoxMethod "reorderChildAfter" o = BoxReorderChildAfterMethodInfo
    ResolveBoxMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveBoxMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveBoxMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveBoxMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveBoxMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveBoxMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveBoxMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveBoxMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveBoxMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveBoxMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveBoxMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveBoxMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveBoxMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveBoxMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveBoxMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveBoxMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveBoxMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveBoxMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveBoxMethod "updateNextAccessibleSibling" o = Gtk.Accessible.AccessibleUpdateNextAccessibleSiblingMethodInfo
    ResolveBoxMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveBoxMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveBoxMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveBoxMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBoxMethod "getAccessibleParent" o = Gtk.Accessible.AccessibleGetAccessibleParentMethodInfo
    ResolveBoxMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveBoxMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveBoxMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveBoxMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveBoxMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveBoxMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveBoxMethod "getAtContext" o = Gtk.Accessible.AccessibleGetAtContextMethodInfo
    ResolveBoxMethod "getBaselinePosition" o = BoxGetBaselinePositionMethodInfo
    ResolveBoxMethod "getBounds" o = Gtk.Accessible.AccessibleGetBoundsMethodInfo
    ResolveBoxMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveBoxMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveBoxMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveBoxMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveBoxMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveBoxMethod "getColor" o = Gtk.Widget.WidgetGetColorMethodInfo
    ResolveBoxMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveBoxMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveBoxMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveBoxMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveBoxMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveBoxMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveBoxMethod "getFirstAccessibleChild" o = Gtk.Accessible.AccessibleGetFirstAccessibleChildMethodInfo
    ResolveBoxMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveBoxMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveBoxMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveBoxMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveBoxMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveBoxMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveBoxMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveBoxMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveBoxMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveBoxMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveBoxMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveBoxMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveBoxMethod "getHomogeneous" o = BoxGetHomogeneousMethodInfo
    ResolveBoxMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveBoxMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveBoxMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveBoxMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveBoxMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveBoxMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveBoxMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveBoxMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveBoxMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveBoxMethod "getNextAccessibleSibling" o = Gtk.Accessible.AccessibleGetNextAccessibleSiblingMethodInfo
    ResolveBoxMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveBoxMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveBoxMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveBoxMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveBoxMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveBoxMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveBoxMethod "getPlatformState" o = Gtk.Accessible.AccessibleGetPlatformStateMethodInfo
    ResolveBoxMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveBoxMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveBoxMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveBoxMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveBoxMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveBoxMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveBoxMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveBoxMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveBoxMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveBoxMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveBoxMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveBoxMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveBoxMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveBoxMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveBoxMethod "getSpacing" o = BoxGetSpacingMethodInfo
    ResolveBoxMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveBoxMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveBoxMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveBoxMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveBoxMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveBoxMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveBoxMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveBoxMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveBoxMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveBoxMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveBoxMethod "setAccessibleParent" o = Gtk.Accessible.AccessibleSetAccessibleParentMethodInfo
    ResolveBoxMethod "setBaselinePosition" o = BoxSetBaselinePositionMethodInfo
    ResolveBoxMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveBoxMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveBoxMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveBoxMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveBoxMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveBoxMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveBoxMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveBoxMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveBoxMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveBoxMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveBoxMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveBoxMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveBoxMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveBoxMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveBoxMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveBoxMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveBoxMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveBoxMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveBoxMethod "setHomogeneous" o = BoxSetHomogeneousMethodInfo
    ResolveBoxMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveBoxMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveBoxMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveBoxMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveBoxMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveBoxMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveBoxMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveBoxMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveBoxMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveBoxMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveBoxMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveBoxMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveBoxMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveBoxMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveBoxMethod "setSpacing" o = BoxSetSpacingMethodInfo
    ResolveBoxMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveBoxMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveBoxMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveBoxMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveBoxMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveBoxMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveBoxMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveBoxMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "baseline-position"
   -- Type: TInterface (Name {namespace = "Gtk", name = "BaselinePosition"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

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

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

#if defined(ENABLE_OVERLOADING)
data BoxBaselinePositionPropertyInfo
instance AttrInfo BoxBaselinePositionPropertyInfo where
    type AttrAllowedOps BoxBaselinePositionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxBaselinePositionPropertyInfo = IsBox
    type AttrSetTypeConstraint BoxBaselinePositionPropertyInfo = (~) Gtk.Enums.BaselinePosition
    type AttrTransferTypeConstraint BoxBaselinePositionPropertyInfo = (~) Gtk.Enums.BaselinePosition
    type AttrTransferType BoxBaselinePositionPropertyInfo = Gtk.Enums.BaselinePosition
    type AttrGetType BoxBaselinePositionPropertyInfo = Gtk.Enums.BaselinePosition
    type AttrLabel BoxBaselinePositionPropertyInfo = "baseline-position"
    type AttrOrigin BoxBaselinePositionPropertyInfo = Box
    attrGet = getBoxBaselinePosition
    attrSet = setBoxBaselinePosition
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxBaselinePosition
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.baselinePosition"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#g:attr:baselinePosition"
        })
#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' box #homogeneous
-- @
getBoxHomogeneous :: (MonadIO m, IsBox o) => o -> m Bool
getBoxHomogeneous :: forall (m :: * -> *) o. (MonadIO m, IsBox o) => o -> m Bool
getBoxHomogeneous o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"homogeneous"

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

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

#if defined(ENABLE_OVERLOADING)
data BoxHomogeneousPropertyInfo
instance AttrInfo BoxHomogeneousPropertyInfo where
    type AttrAllowedOps BoxHomogeneousPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxHomogeneousPropertyInfo = IsBox
    type AttrSetTypeConstraint BoxHomogeneousPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint BoxHomogeneousPropertyInfo = (~) Bool
    type AttrTransferType BoxHomogeneousPropertyInfo = Bool
    type AttrGetType BoxHomogeneousPropertyInfo = Bool
    type AttrLabel BoxHomogeneousPropertyInfo = "homogeneous"
    type AttrOrigin BoxHomogeneousPropertyInfo = Box
    attrGet = getBoxHomogeneous
    attrSet = setBoxHomogeneous
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxHomogeneous
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.homogeneous"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#g:attr:homogeneous"
        })
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data BoxSpacingPropertyInfo
instance AttrInfo BoxSpacingPropertyInfo where
    type AttrAllowedOps BoxSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint BoxSpacingPropertyInfo = IsBox
    type AttrSetTypeConstraint BoxSpacingPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint BoxSpacingPropertyInfo = (~) Int32
    type AttrTransferType BoxSpacingPropertyInfo = Int32
    type AttrGetType BoxSpacingPropertyInfo = Int32
    type AttrLabel BoxSpacingPropertyInfo = "spacing"
    type AttrOrigin BoxSpacingPropertyInfo = Box
    attrGet = getBoxSpacing
    attrSet = setBoxSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructBoxSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.spacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#g:attr:spacing"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Box
type instance O.AttributeList Box = BoxAttributeList
type BoxAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("baselinePosition", BoxBaselinePositionPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("homogeneous", BoxHomogeneousPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("spacing", BoxSpacingPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
boxBaselinePosition :: AttrLabelProxy "baselinePosition"
boxBaselinePosition = AttrLabelProxy

boxHomogeneous :: AttrLabelProxy "homogeneous"
boxHomogeneous = AttrLabelProxy

boxSpacing :: AttrLabelProxy "spacing"
boxSpacing = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Box = BoxSignalList
type BoxSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Box::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "orientation"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Orientation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the box\8217s orientation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spacing"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of pixels to place by default between children"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Box" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_new" gtk_box_new :: 
    CUInt ->                                -- orientation : TInterface (Name {namespace = "Gtk", name = "Orientation"})
    Int32 ->                                -- spacing : TBasicType TInt
    IO (Ptr Box)

-- | Creates a new @GtkBox@.
boxNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gtk.Enums.Orientation
    -- ^ /@orientation@/: the box’s orientation
    -> Int32
    -- ^ /@spacing@/: the number of pixels to place by default between children
    -> m Box
    -- ^ __Returns:__ a new @GtkBox@.
boxNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Orientation -> Int32 -> m Box
boxNew Orientation
orientation Int32
spacing = IO Box -> m Box
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Box -> m Box) -> IO Box -> m Box
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) -> (Orientation -> Int) -> Orientation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Orientation -> Int
forall a. Enum a => a -> Int
fromEnum) Orientation
orientation
    Ptr Box
result <- CUInt -> Int32 -> IO (Ptr Box)
gtk_box_new CUInt
orientation' Int32
spacing
    Text -> Ptr Box -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"boxNew" Ptr Box
result
    Box
result' <- ((ManagedPtr Box -> Box) -> Ptr Box -> IO Box
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Box -> Box
Box) Ptr Box
result
    Box -> IO Box
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Box::append
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkWidget` to append"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_append" gtk_box_append :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Adds /@child@/ as the last child to /@box@/.
boxAppend ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> b
    -- ^ /@child@/: the @GtkWidget@ to append
    -> m ()
boxAppend :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBox a, IsWidget b) =>
a -> b -> m ()
boxAppend a
box b
child = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr Box -> Ptr Widget -> IO ()
gtk_box_append Ptr Box
box' Ptr Widget
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxAppendMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsBox a, Gtk.Widget.IsWidget b) => O.OverloadedMethod BoxAppendMethodInfo a signature where
    overloadedMethod = boxAppend

instance O.OverloadedMethodInfo BoxAppendMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxAppend",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxAppend"
        })


#endif

-- method Box::get_baseline_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "BaselinePosition" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_get_baseline_position" gtk_box_get_baseline_position :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    IO CUInt

-- | Gets the value set by 'GI.Gtk.Objects.Box.boxSetBaselinePosition'.
boxGetBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> m Gtk.Enums.BaselinePosition
    -- ^ __Returns:__ the baseline position
boxGetBaselinePosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBox a) =>
a -> m BaselinePosition
boxGetBaselinePosition a
box = IO BaselinePosition -> m BaselinePosition
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BaselinePosition -> m BaselinePosition)
-> IO BaselinePosition -> m BaselinePosition
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    CUInt
result <- Ptr Box -> IO CUInt
gtk_box_get_baseline_position Ptr Box
box'
    let result' :: BaselinePosition
result' = (Int -> BaselinePosition
forall a. Enum a => Int -> a
toEnum (Int -> BaselinePosition)
-> (CUInt -> Int) -> CUInt -> BaselinePosition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    BaselinePosition -> IO BaselinePosition
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BaselinePosition
result'

#if defined(ENABLE_OVERLOADING)
data BoxGetBaselinePositionMethodInfo
instance (signature ~ (m Gtk.Enums.BaselinePosition), MonadIO m, IsBox a) => O.OverloadedMethod BoxGetBaselinePositionMethodInfo a signature where
    overloadedMethod = boxGetBaselinePosition

instance O.OverloadedMethodInfo BoxGetBaselinePositionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxGetBaselinePosition",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxGetBaselinePosition"
        })


#endif

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

foreign import ccall "gtk_box_get_homogeneous" gtk_box_get_homogeneous :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    IO CInt

-- | Returns whether the box is homogeneous (all children are the
-- same size).
boxGetHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the box is homogeneous.
boxGetHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBox a) =>
a -> m Bool
boxGetHomogeneous a
box = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    CInt
result <- Ptr Box -> IO CInt
gtk_box_get_homogeneous Ptr Box
box'
    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
box
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BoxGetHomogeneousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsBox a) => O.OverloadedMethod BoxGetHomogeneousMethodInfo a signature where
    overloadedMethod = boxGetHomogeneous

instance O.OverloadedMethodInfo BoxGetHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxGetHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxGetHomogeneous"
        })


#endif

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

foreign import ccall "gtk_box_get_spacing" gtk_box_get_spacing :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    IO Int32

-- | Gets the value set by 'GI.Gtk.Objects.Box.boxSetSpacing'.
boxGetSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> m Int32
    -- ^ __Returns:__ spacing between children
boxGetSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBox a) =>
a -> m Int32
boxGetSpacing a
box = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    Int32
result <- Ptr Box -> IO Int32
gtk_box_get_spacing Ptr Box
box'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data BoxGetSpacingMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsBox a) => O.OverloadedMethod BoxGetSpacingMethodInfo a signature where
    overloadedMethod = boxGetSpacing

instance O.OverloadedMethodInfo BoxGetSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxGetSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxGetSpacing"
        })


#endif

-- method Box::insert_child_after
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkWidget` to insert"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sibling"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the sibling after which to insert @child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_insert_child_after" gtk_box_insert_child_after :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    Ptr Gtk.Widget.Widget ->                -- sibling : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Inserts /@child@/ in the position after /@sibling@/ in the list
-- of /@box@/ children.
-- 
-- If /@sibling@/ is 'P.Nothing', insert /@child@/ at the first position.
boxInsertChildAfter ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a, Gtk.Widget.IsWidget b, Gtk.Widget.IsWidget c) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> b
    -- ^ /@child@/: the @GtkWidget@ to insert
    -> Maybe (c)
    -- ^ /@sibling@/: the sibling after which to insert /@child@/
    -> m ()
boxInsertChildAfter :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsBox a, IsWidget b, IsWidget c) =>
a -> b -> Maybe c -> m ()
boxInsertChildAfter a
box b
child Maybe c
sibling = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr Widget
maybeSibling <- case Maybe c
sibling of
        Maybe c
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just c
jSibling -> do
            Ptr Widget
jSibling' <- c -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jSibling
            Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jSibling'
    Ptr Box -> Ptr Widget -> Ptr Widget -> IO ()
gtk_box_insert_child_after Ptr Box
box' Ptr Widget
child' Ptr Widget
maybeSibling
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
sibling c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxInsertChildAfterMethodInfo
instance (signature ~ (b -> Maybe (c) -> m ()), MonadIO m, IsBox a, Gtk.Widget.IsWidget b, Gtk.Widget.IsWidget c) => O.OverloadedMethod BoxInsertChildAfterMethodInfo a signature where
    overloadedMethod = boxInsertChildAfter

instance O.OverloadedMethodInfo BoxInsertChildAfterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxInsertChildAfter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxInsertChildAfter"
        })


#endif

-- method Box::prepend
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkWidget` to prepend"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_prepend" gtk_box_prepend :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Adds /@child@/ as the first child to /@box@/.
boxPrepend ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> b
    -- ^ /@child@/: the @GtkWidget@ to prepend
    -> m ()
boxPrepend :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBox a, IsWidget b) =>
a -> b -> m ()
boxPrepend a
box b
child = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr Box -> Ptr Widget -> IO ()
gtk_box_prepend Ptr Box
box' Ptr Widget
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxPrependMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsBox a, Gtk.Widget.IsWidget b) => O.OverloadedMethod BoxPrependMethodInfo a signature where
    overloadedMethod = boxPrepend

instance O.OverloadedMethodInfo BoxPrependMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxPrepend",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxPrepend"
        })


#endif

-- method Box::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_remove" gtk_box_remove :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Removes a child widget from /@box@/.
-- 
-- The child must have been added before with
-- 'GI.Gtk.Objects.Box.boxAppend', 'GI.Gtk.Objects.Box.boxPrepend', or
-- 'GI.Gtk.Objects.Box.boxInsertChildAfter'.
boxRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> b
    -- ^ /@child@/: the child to remove
    -> m ()
boxRemove :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsBox a, IsWidget b) =>
a -> b -> m ()
boxRemove a
box b
child = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr Box -> Ptr Widget -> IO ()
gtk_box_remove Ptr Box
box' Ptr Widget
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxRemoveMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsBox a, Gtk.Widget.IsWidget b) => O.OverloadedMethod BoxRemoveMethodInfo a signature where
    overloadedMethod = boxRemove

instance O.OverloadedMethodInfo BoxRemoveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxRemove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxRemove"
        })


#endif

-- method Box::reorder_child_after
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the `GtkWidget` to move, must be a child of @box"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sibling"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the sibling to move @child after"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_reorder_child_after" gtk_box_reorder_child_after :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    Ptr Gtk.Widget.Widget ->                -- sibling : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Moves /@child@/ to the position after /@sibling@/ in the list
-- of /@box@/ children.
-- 
-- If /@sibling@/ is 'P.Nothing', move /@child@/ to the first position.
boxReorderChildAfter ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a, Gtk.Widget.IsWidget b, Gtk.Widget.IsWidget c) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> b
    -- ^ /@child@/: the @GtkWidget@ to move, must be a child of /@box@/
    -> Maybe (c)
    -- ^ /@sibling@/: the sibling to move /@child@/ after
    -> m ()
boxReorderChildAfter :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsBox a, IsWidget b, IsWidget c) =>
a -> b -> Maybe c -> m ()
boxReorderChildAfter a
box b
child Maybe c
sibling = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr Widget
maybeSibling <- case Maybe c
sibling of
        Maybe c
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just c
jSibling -> do
            Ptr Widget
jSibling' <- c -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jSibling
            Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jSibling'
    Ptr Box -> Ptr Widget -> Ptr Widget -> IO ()
gtk_box_reorder_child_after Ptr Box
box' Ptr Widget
child' Ptr Widget
maybeSibling
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
sibling c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxReorderChildAfterMethodInfo
instance (signature ~ (b -> Maybe (c) -> m ()), MonadIO m, IsBox a, Gtk.Widget.IsWidget b, Gtk.Widget.IsWidget c) => O.OverloadedMethod BoxReorderChildAfterMethodInfo a signature where
    overloadedMethod = boxReorderChildAfter

instance O.OverloadedMethodInfo BoxReorderChildAfterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxReorderChildAfter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxReorderChildAfter"
        })


#endif

-- method Box::set_baseline_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BaselinePosition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBaselinePosition`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_set_baseline_position" gtk_box_set_baseline_position :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    CUInt ->                                -- position : TInterface (Name {namespace = "Gtk", name = "BaselinePosition"})
    IO ()

-- | Sets the baseline position of a box.
-- 
-- This affects only horizontal boxes with at least one baseline
-- aligned child. If there is more vertical space available than
-- requested, and the baseline is not allocated by the parent then
-- /@position@/ is used to allocate the baseline with respect to the
-- extra space available.
boxSetBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> Gtk.Enums.BaselinePosition
    -- ^ /@position@/: a @GtkBaselinePosition@
    -> m ()
boxSetBaselinePosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBox a) =>
a -> BaselinePosition -> m ()
boxSetBaselinePosition a
box BaselinePosition
position = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    let position' :: CUInt
position' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (BaselinePosition -> Int) -> BaselinePosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BaselinePosition -> Int
forall a. Enum a => a -> Int
fromEnum) BaselinePosition
position
    Ptr Box -> CUInt -> IO ()
gtk_box_set_baseline_position Ptr Box
box' CUInt
position'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxSetBaselinePositionMethodInfo
instance (signature ~ (Gtk.Enums.BaselinePosition -> m ()), MonadIO m, IsBox a) => O.OverloadedMethod BoxSetBaselinePositionMethodInfo a signature where
    overloadedMethod = boxSetBaselinePosition

instance O.OverloadedMethodInfo BoxSetBaselinePositionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxSetBaselinePosition",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxSetBaselinePosition"
        })


#endif

-- method Box::set_homogeneous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , 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
--                       "a boolean value, %TRUE to create equal allotments,\n  %FALSE for variable allotments"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_set_homogeneous" gtk_box_set_homogeneous :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    CInt ->                                 -- homogeneous : TBasicType TBoolean
    IO ()

-- | Sets whether or not all children of /@box@/ are given equal space
-- in the box.
boxSetHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> Bool
    -- ^ /@homogeneous@/: a boolean value, 'P.True' to create equal allotments,
    --   'P.False' for variable allotments
    -> m ()
boxSetHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBox a) =>
a -> Bool -> m ()
boxSetHomogeneous a
box Bool
homogeneous = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    let homogeneous' :: CInt
homogeneous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
homogeneous
    Ptr Box -> CInt -> IO ()
gtk_box_set_homogeneous Ptr Box
box' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxSetHomogeneousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsBox a) => O.OverloadedMethod BoxSetHomogeneousMethodInfo a signature where
    overloadedMethod = boxSetHomogeneous

instance O.OverloadedMethodInfo BoxSetHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxSetHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxSetHomogeneous"
        })


#endif

-- method Box::set_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "box"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Box" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBox`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spacing"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of pixels to put between children"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_box_set_spacing" gtk_box_set_spacing :: 
    Ptr Box ->                              -- box : TInterface (Name {namespace = "Gtk", name = "Box"})
    Int32 ->                                -- spacing : TBasicType TInt
    IO ()

-- | Sets the number of pixels to place between children of /@box@/.
boxSetSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a @GtkBox@
    -> Int32
    -- ^ /@spacing@/: the number of pixels to put between children
    -> m ()
boxSetSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBox a) =>
a -> Int32 -> m ()
boxSetSpacing a
box Int32
spacing = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Box
box' <- a -> IO (Ptr Box)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
box
    Ptr Box -> Int32 -> IO ()
gtk_box_set_spacing Ptr Box
box' Int32
spacing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxSetSpacingMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsBox a) => O.OverloadedMethod BoxSetSpacingMethodInfo a signature where
    overloadedMethod = boxSetSpacing

instance O.OverloadedMethodInfo BoxSetSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Box.boxSetSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Box.html#v:boxSetSpacing"
        })


#endif