{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GtkBox widget arranges child widgets into a single row or column,
-- depending upon 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 t'GI.Gtk.Objects.Widget.Widget':@/halign/@ and t'GI.Gtk.Objects.Widget.Widget':@/valign/@ properties can be used on
-- the children to influence their allocation.
-- 
-- Use repeated calls to 'GI.Gtk.Objects.Container.containerAdd' to pack widgets into a
-- GtkBox from start to end. Use 'GI.Gtk.Objects.Container.containerRemove' 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.

#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                                   ,
    noBox                                   ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveBoxMethod                        ,
#endif


-- ** 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                                  ,


-- ** 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#
-- | /No description available in the introspection data./

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


-- ** homogeneous #attr:homogeneous#
-- | /No description available in the introspection data./

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


-- ** spacing #attr:spacing#
-- | /No description available in the introspection data./

#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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

-- | Memory-managed wrapper type.
newtype Box = Box (ManagedPtr Box)
    deriving (Box -> Box -> Bool
(Box -> Box -> Bool) -> (Box -> Box -> Bool) -> Eq Box
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Box -> Box -> Bool
$c/= :: Box -> Box -> Bool
== :: Box -> Box -> Bool
$c== :: Box -> Box -> Bool
Eq)
foreign import ccall "gtk_box_get_type"
    c_gtk_box_get_type :: IO GType

instance GObject Box where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_box_get_type
    

-- | Convert 'Box' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Box where
    toGValue :: Box -> IO GValue
toGValue o :: Box
o = do
        GType
gtype <- IO GType
c_gtk_box_get_type
        Box -> (Ptr Box -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Box
o (GType -> (GValue -> Ptr Box -> IO ()) -> Ptr Box -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Box -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Box
fromGValue gv :: GValue
gv = do
        Ptr Box
ptr <- GValue -> IO (Ptr Box)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Box)
        (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
        
    

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

instance O.HasParentTypes Box
type instance O.ParentTypes Box = '[Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, 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 :: (MonadIO m, IsBox o) => o -> m Box
toBox :: o -> m Box
toBox = IO Box -> m Box
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Box -> Box
Box

-- | A convenience alias for `Nothing` :: `Maybe` `Box`.
noBox :: Maybe Box
noBox :: Maybe Box
noBox = Maybe Box
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveBoxMethod (t :: Symbol) (o :: *) :: * where
    ResolveBoxMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveBoxMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveBoxMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveBoxMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolveBoxMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveBoxMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveBoxMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveBoxMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveBoxMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveBoxMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveBoxMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBoxMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBoxMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveBoxMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveBoxMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    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 "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveBoxMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveBoxMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveBoxMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveBoxMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveBoxMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveBoxMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveBoxMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveBoxMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveBoxMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveBoxMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveBoxMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveBoxMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveBoxMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveBoxMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveBoxMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveBoxMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveBoxMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveBoxMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveBoxMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveBoxMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveBoxMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveBoxMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveBoxMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveBoxMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveBoxMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveBoxMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveBoxMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveBoxMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveBoxMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveBoxMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveBoxMethod "dragSourceSetIconPaintable" o = Gtk.Widget.WidgetDragSourceSetIconPaintableMethodInfo
    ResolveBoxMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveBoxMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveBoxMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveBoxMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveBoxMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveBoxMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolveBoxMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBoxMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolveBoxMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBoxMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBoxMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveBoxMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveBoxMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveBoxMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveBoxMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveBoxMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    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 "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    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 "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveBoxMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveBoxMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveBoxMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveBoxMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    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 "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveBoxMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveBoxMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveBoxMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveBoxMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveBoxMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveBoxMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveBoxMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveBoxMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBoxMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBoxMethod "registerSurface" o = Gtk.Widget.WidgetRegisterSurfaceMethodInfo
    ResolveBoxMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolveBoxMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveBoxMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveBoxMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveBoxMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveBoxMethod "reorderChildAfter" o = BoxReorderChildAfterMethodInfo
    ResolveBoxMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveBoxMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    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 "unregisterSurface" o = Gtk.Widget.WidgetUnregisterSurfaceMethodInfo
    ResolveBoxMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveBoxMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBoxMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveBoxMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    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 "getBaselinePosition" o = BoxGetBaselinePositionMethodInfo
    ResolveBoxMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveBoxMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveBoxMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveBoxMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolveBoxMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    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 "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveBoxMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveBoxMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolveBoxMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveBoxMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    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 "getHasSurface" o = Gtk.Widget.WidgetGetHasSurfaceMethodInfo
    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 "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    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 "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveBoxMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    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 "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveBoxMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    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 "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveBoxMethod "getSpacing" o = BoxGetSpacingMethodInfo
    ResolveBoxMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveBoxMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveBoxMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveBoxMethod "getSurface" o = Gtk.Widget.WidgetGetSurfaceMethodInfo
    ResolveBoxMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveBoxMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveBoxMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveBoxMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveBoxMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    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 "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveBoxMethod "setBaselinePosition" o = BoxSetBaselinePositionMethodInfo
    ResolveBoxMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveBoxMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveBoxMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveBoxMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    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 "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolveBoxMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveBoxMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolveBoxMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveBoxMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveBoxMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveBoxMethod "setHasSurface" o = Gtk.Widget.WidgetSetHasSurfaceMethodInfo
    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 "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveBoxMethod "setSurface" o = Gtk.Widget.WidgetSetSurfaceMethodInfo
    ResolveBoxMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveBoxMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveBoxMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    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.MethodInfo 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

#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 :: o -> m BaselinePosition
getBoxBaselinePosition obj :: o
obj = IO BaselinePosition -> m BaselinePosition
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
$ o -> String -> IO BaselinePosition
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "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 :: o -> BaselinePosition -> m ()
setBoxBaselinePosition obj :: o
obj val :: BaselinePosition
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> BaselinePosition -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj "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) => Gtk.Enums.BaselinePosition -> IO (GValueConstruct o)
constructBoxBaselinePosition :: BaselinePosition -> IO (GValueConstruct o)
constructBoxBaselinePosition val :: BaselinePosition
val = String -> BaselinePosition -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "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
#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 :: o -> m Bool
getBoxHomogeneous obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "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 :: o -> Bool -> m ()
setBoxHomogeneous obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "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) => Bool -> IO (GValueConstruct o)
constructBoxHomogeneous :: Bool -> IO (GValueConstruct o)
constructBoxHomogeneous val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "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
#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 :: o -> m Int32
getBoxSpacing obj :: o
obj = IO Int32 -> m Int32
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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "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 :: o -> Int32 -> m ()
setBoxSpacing obj :: o
obj val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "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) => Int32 -> IO (GValueConstruct o)
constructBoxSpacing :: Int32 -> IO (GValueConstruct o)
constructBoxSpacing val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "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
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Box
type instance O.AttributeList Box = BoxAttributeList
type BoxAttributeList = ('[ '("baselinePosition", BoxBaselinePositionPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("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), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("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), '("surface", Gtk.Widget.WidgetSurfacePropertyInfo), '("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, *)])
#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 = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#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 t'GI.Gtk.Objects.Box.Box'.
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 t'GI.Gtk.Objects.Box.Box'.
boxNew :: Orientation -> Int32 -> m Box
boxNew orientation :: Orientation
orientation spacing :: Int32
spacing = IO Box -> m Box
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 "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 (m :: * -> *) a. Monad m => a -> m a
return Box
result'

#if defined(ENABLE_OVERLOADING)
#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 t'GI.Gtk.Objects.Box.Box'
    -> m Gtk.Enums.BaselinePosition
    -- ^ __Returns:__ the baseline position
boxGetBaselinePosition :: a -> m BaselinePosition
boxGetBaselinePosition box :: a
box = IO BaselinePosition -> m BaselinePosition
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 (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.MethodInfo BoxGetBaselinePositionMethodInfo a signature where
    overloadedMethod = 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). See 'GI.Gtk.Objects.Box.boxSetHomogeneous'.
boxGetHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a t'GI.Gtk.Objects.Box.Box'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the box is homogeneous.
boxGetHomogeneous :: a -> m Bool
boxGetHomogeneous box :: a
box = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
box
    Bool -> IO Bool
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.MethodInfo BoxGetHomogeneousMethodInfo a signature where
    overloadedMethod = 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 t'GI.Gtk.Objects.Box.Box'
    -> m Int32
    -- ^ __Returns:__ spacing between children
boxGetSpacing :: a -> m Int32
boxGetSpacing box :: a
box = IO Int32 -> m Int32
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 (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.MethodInfo BoxGetSpacingMethodInfo a signature where
    overloadedMethod = 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 to move @child after, or %NULL"
--                 , 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 t'GI.Gtk.Objects.Box.Box'
    -> b
    -- ^ /@child@/: the t'GI.Gtk.Objects.Widget.Widget' to insert
    -> Maybe (c)
    -- ^ /@sibling@/: the sibling to move /@child@/ after, or 'P.Nothing'
    -> m ()
boxInsertChildAfter :: a -> b -> Maybe c -> m ()
boxInsertChildAfter box :: a
box child :: b
child sibling :: Maybe c
sibling = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
        Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just jSibling :: 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 (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 (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.MethodInfo BoxInsertChildAfterMethodInfo a signature where
    overloadedMethod = boxInsertChildAfter

#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, or %NULL"
--                 , 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 t'GI.Gtk.Objects.Box.Box'
    -> b
    -- ^ /@child@/: the t'GI.Gtk.Objects.Widget.Widget' to move, must be a child of /@box@/
    -> Maybe (c)
    -- ^ /@sibling@/: the sibling to move /@child@/ after, or 'P.Nothing'
    -> m ()
boxReorderChildAfter :: a -> b -> Maybe c -> m ()
boxReorderChildAfter box :: a
box child :: b
child sibling :: Maybe c
sibling = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
        Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just jSibling :: 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 (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 (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.MethodInfo BoxReorderChildAfterMethodInfo a signature where
    overloadedMethod = 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 wrt the
-- extra space available.
boxSetBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a t'GI.Gtk.Objects.Box.Box'
    -> Gtk.Enums.BaselinePosition
    -- ^ /@position@/: a t'GI.Gtk.Enums.BaselinePosition'
    -> m ()
boxSetBaselinePosition :: a -> BaselinePosition -> m ()
boxSetBaselinePosition box :: a
box position :: BaselinePosition
position = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo BoxSetBaselinePositionMethodInfo a signature where
    overloadedMethod = 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 the t'GI.Gtk.Objects.Box.Box':@/homogeneous/@ property of /@box@/, controlling
-- 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 t'GI.Gtk.Objects.Box.Box'
    -> Bool
    -- ^ /@homogeneous@/: a boolean value, 'P.True' to create equal allotments,
    --   'P.False' for variable allotments
    -> m ()
boxSetHomogeneous :: a -> Bool -> m ()
boxSetHomogeneous box :: a
box homogeneous :: Bool
homogeneous = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
homogeneous
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BoxSetHomogeneousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsBox a) => O.MethodInfo BoxSetHomogeneousMethodInfo a signature where
    overloadedMethod = 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 t'GI.Gtk.Objects.Box.Box':@/spacing/@ property of /@box@/, which is the
-- number of pixels to place between children of /@box@/.
boxSetSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsBox a) =>
    a
    -- ^ /@box@/: a t'GI.Gtk.Objects.Box.Box'
    -> Int32
    -- ^ /@spacing@/: the number of pixels to put between children
    -> m ()
boxSetSpacing :: a -> Int32 -> m ()
boxSetSpacing box :: a
box spacing :: Int32
spacing = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif