{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GtkCenterBox widget arranges three children in a horizontal
-- or vertical arrangement, keeping the middle child centered as well
-- as possible.
-- 
-- To add children to GtkCenterBox, use 'GI.Gtk.Objects.CenterBox.centerBoxSetStartWidget',
-- 'GI.Gtk.Objects.CenterBox.centerBoxSetCenterWidget' and 'GI.Gtk.Objects.CenterBox.centerBoxSetEndWidget'.
-- 
-- The sizing and positioning of children can be influenced with the
-- align and expand properties of the children.
-- 
-- = GtkCenterBox as GtkBuildable
-- 
-- The GtkCenterBox implementation of the t'GI.Gtk.Interfaces.Buildable.Buildable' interface supports
-- placing children in the 3 positions by specifying “start”, “center” or
-- “end” as the “type” attribute of a \<child> element.
-- 
-- = CSS nodes
-- 
-- GtkCenterBox uses a single CSS node with the name “box”,
-- 
-- The first child of the t'GI.Gtk.Objects.CenterBox.CenterBox' will be allocated depending on the
-- text direction, i.e. in left-to-right layouts it will be allocated on the
-- left and in right-to-left layouts on the right.
-- 
-- In vertical orientation, the nodes of the children are arranged from top to
-- bottom.

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

module GI.Gtk.Objects.CenterBox
    ( 

-- * Exported types
    CenterBox(..)                           ,
    IsCenterBox                             ,
    toCenterBox                             ,
    noCenterBox                             ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveCenterBoxMethod                  ,
#endif


-- ** getBaselinePosition #method:getBaselinePosition#

#if defined(ENABLE_OVERLOADING)
    CenterBoxGetBaselinePositionMethodInfo  ,
#endif
    centerBoxGetBaselinePosition            ,


-- ** getCenterWidget #method:getCenterWidget#

#if defined(ENABLE_OVERLOADING)
    CenterBoxGetCenterWidgetMethodInfo      ,
#endif
    centerBoxGetCenterWidget                ,


-- ** getEndWidget #method:getEndWidget#

#if defined(ENABLE_OVERLOADING)
    CenterBoxGetEndWidgetMethodInfo         ,
#endif
    centerBoxGetEndWidget                   ,


-- ** getStartWidget #method:getStartWidget#

#if defined(ENABLE_OVERLOADING)
    CenterBoxGetStartWidgetMethodInfo       ,
#endif
    centerBoxGetStartWidget                 ,


-- ** new #method:new#

    centerBoxNew                            ,


-- ** setBaselinePosition #method:setBaselinePosition#

#if defined(ENABLE_OVERLOADING)
    CenterBoxSetBaselinePositionMethodInfo  ,
#endif
    centerBoxSetBaselinePosition            ,


-- ** setCenterWidget #method:setCenterWidget#

#if defined(ENABLE_OVERLOADING)
    CenterBoxSetCenterWidgetMethodInfo      ,
#endif
    centerBoxSetCenterWidget                ,


-- ** setEndWidget #method:setEndWidget#

#if defined(ENABLE_OVERLOADING)
    CenterBoxSetEndWidgetMethodInfo         ,
#endif
    centerBoxSetEndWidget                   ,


-- ** setStartWidget #method:setStartWidget#

#if defined(ENABLE_OVERLOADING)
    CenterBoxSetStartWidgetMethodInfo       ,
#endif
    centerBoxSetStartWidget                 ,




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

#if defined(ENABLE_OVERLOADING)
    CenterBoxBaselinePositionPropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    centerBoxBaselinePosition               ,
#endif
    constructCenterBoxBaselinePosition      ,
    getCenterBoxBaselinePosition            ,
    setCenterBoxBaselinePosition            ,




    ) 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.Widget as Gtk.Widget

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

instance GObject CenterBox where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_center_box_get_type
    

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

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

instance O.HasParentTypes CenterBox
type instance O.ParentTypes CenterBox = '[Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.Orientable.Orientable]

-- | Cast to `CenterBox`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toCenterBox :: (MonadIO m, IsCenterBox o) => o -> m CenterBox
toCenterBox :: o -> m CenterBox
toCenterBox = IO CenterBox -> m CenterBox
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CenterBox -> m CenterBox)
-> (o -> IO CenterBox) -> o -> m CenterBox
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr CenterBox -> CenterBox) -> o -> IO CenterBox
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr CenterBox -> CenterBox
CenterBox

-- | A convenience alias for `Nothing` :: `Maybe` `CenterBox`.
noCenterBox :: Maybe CenterBox
noCenterBox :: Maybe CenterBox
noCenterBox = Maybe CenterBox
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveCenterBoxMethod (t :: Symbol) (o :: *) :: * where
    ResolveCenterBoxMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveCenterBoxMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveCenterBoxMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveCenterBoxMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveCenterBoxMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveCenterBoxMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveCenterBoxMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveCenterBoxMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveCenterBoxMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveCenterBoxMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCenterBoxMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCenterBoxMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveCenterBoxMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveCenterBoxMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveCenterBoxMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveCenterBoxMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveCenterBoxMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveCenterBoxMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveCenterBoxMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveCenterBoxMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveCenterBoxMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveCenterBoxMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveCenterBoxMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveCenterBoxMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveCenterBoxMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveCenterBoxMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveCenterBoxMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveCenterBoxMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveCenterBoxMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveCenterBoxMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveCenterBoxMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveCenterBoxMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveCenterBoxMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveCenterBoxMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveCenterBoxMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveCenterBoxMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveCenterBoxMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveCenterBoxMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveCenterBoxMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveCenterBoxMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveCenterBoxMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveCenterBoxMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveCenterBoxMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveCenterBoxMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveCenterBoxMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveCenterBoxMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveCenterBoxMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveCenterBoxMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveCenterBoxMethod "dragSourceSetIconPaintable" o = Gtk.Widget.WidgetDragSourceSetIconPaintableMethodInfo
    ResolveCenterBoxMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveCenterBoxMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveCenterBoxMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveCenterBoxMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveCenterBoxMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveCenterBoxMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCenterBoxMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCenterBoxMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCenterBoxMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveCenterBoxMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveCenterBoxMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveCenterBoxMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveCenterBoxMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveCenterBoxMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveCenterBoxMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveCenterBoxMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveCenterBoxMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveCenterBoxMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveCenterBoxMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveCenterBoxMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveCenterBoxMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveCenterBoxMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveCenterBoxMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveCenterBoxMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveCenterBoxMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCenterBoxMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveCenterBoxMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveCenterBoxMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveCenterBoxMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveCenterBoxMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveCenterBoxMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveCenterBoxMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveCenterBoxMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveCenterBoxMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveCenterBoxMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveCenterBoxMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveCenterBoxMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCenterBoxMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCenterBoxMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveCenterBoxMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveCenterBoxMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveCenterBoxMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveCenterBoxMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveCenterBoxMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveCenterBoxMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveCenterBoxMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveCenterBoxMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveCenterBoxMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveCenterBoxMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCenterBoxMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCenterBoxMethod "registerSurface" o = Gtk.Widget.WidgetRegisterSurfaceMethodInfo
    ResolveCenterBoxMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveCenterBoxMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveCenterBoxMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveCenterBoxMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveCenterBoxMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveCenterBoxMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCenterBoxMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveCenterBoxMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveCenterBoxMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveCenterBoxMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCenterBoxMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCenterBoxMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCenterBoxMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveCenterBoxMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveCenterBoxMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveCenterBoxMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveCenterBoxMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveCenterBoxMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCenterBoxMethod "unregisterSurface" o = Gtk.Widget.WidgetUnregisterSurfaceMethodInfo
    ResolveCenterBoxMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveCenterBoxMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCenterBoxMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveCenterBoxMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveCenterBoxMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveCenterBoxMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveCenterBoxMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveCenterBoxMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveCenterBoxMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveCenterBoxMethod "getBaselinePosition" o = CenterBoxGetBaselinePositionMethodInfo
    ResolveCenterBoxMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveCenterBoxMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveCenterBoxMethod "getCenterWidget" o = CenterBoxGetCenterWidgetMethodInfo
    ResolveCenterBoxMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveCenterBoxMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveCenterBoxMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveCenterBoxMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCenterBoxMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveCenterBoxMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveCenterBoxMethod "getEndWidget" o = CenterBoxGetEndWidgetMethodInfo
    ResolveCenterBoxMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveCenterBoxMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveCenterBoxMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveCenterBoxMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveCenterBoxMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveCenterBoxMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveCenterBoxMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveCenterBoxMethod "getHasSurface" o = Gtk.Widget.WidgetGetHasSurfaceMethodInfo
    ResolveCenterBoxMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveCenterBoxMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveCenterBoxMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveCenterBoxMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveCenterBoxMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveCenterBoxMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveCenterBoxMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveCenterBoxMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveCenterBoxMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveCenterBoxMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveCenterBoxMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveCenterBoxMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveCenterBoxMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveCenterBoxMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveCenterBoxMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveCenterBoxMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveCenterBoxMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveCenterBoxMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveCenterBoxMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveCenterBoxMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveCenterBoxMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveCenterBoxMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveCenterBoxMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveCenterBoxMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveCenterBoxMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCenterBoxMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCenterBoxMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveCenterBoxMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveCenterBoxMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveCenterBoxMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveCenterBoxMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveCenterBoxMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveCenterBoxMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveCenterBoxMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveCenterBoxMethod "getStartWidget" o = CenterBoxGetStartWidgetMethodInfo
    ResolveCenterBoxMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveCenterBoxMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveCenterBoxMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveCenterBoxMethod "getSurface" o = Gtk.Widget.WidgetGetSurfaceMethodInfo
    ResolveCenterBoxMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveCenterBoxMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveCenterBoxMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveCenterBoxMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveCenterBoxMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveCenterBoxMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveCenterBoxMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveCenterBoxMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveCenterBoxMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveCenterBoxMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveCenterBoxMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveCenterBoxMethod "setBaselinePosition" o = CenterBoxSetBaselinePositionMethodInfo
    ResolveCenterBoxMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveCenterBoxMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveCenterBoxMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveCenterBoxMethod "setCenterWidget" o = CenterBoxSetCenterWidgetMethodInfo
    ResolveCenterBoxMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveCenterBoxMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveCenterBoxMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveCenterBoxMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCenterBoxMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCenterBoxMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveCenterBoxMethod "setEndWidget" o = CenterBoxSetEndWidgetMethodInfo
    ResolveCenterBoxMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveCenterBoxMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveCenterBoxMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveCenterBoxMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveCenterBoxMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveCenterBoxMethod "setHasSurface" o = Gtk.Widget.WidgetSetHasSurfaceMethodInfo
    ResolveCenterBoxMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveCenterBoxMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveCenterBoxMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveCenterBoxMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveCenterBoxMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveCenterBoxMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveCenterBoxMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveCenterBoxMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveCenterBoxMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveCenterBoxMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveCenterBoxMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveCenterBoxMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveCenterBoxMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveCenterBoxMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCenterBoxMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveCenterBoxMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveCenterBoxMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveCenterBoxMethod "setStartWidget" o = CenterBoxSetStartWidgetMethodInfo
    ResolveCenterBoxMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveCenterBoxMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveCenterBoxMethod "setSurface" o = Gtk.Widget.WidgetSetSurfaceMethodInfo
    ResolveCenterBoxMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveCenterBoxMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveCenterBoxMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveCenterBoxMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveCenterBoxMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveCenterBoxMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveCenterBoxMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveCenterBoxMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveCenterBoxMethod t CenterBox, O.MethodInfo info CenterBox p) => OL.IsLabel t (CenterBox -> 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' centerBox #baselinePosition
-- @
getCenterBoxBaselinePosition :: (MonadIO m, IsCenterBox o) => o -> m Gtk.Enums.BaselinePosition
getCenterBoxBaselinePosition :: o -> m BaselinePosition
getCenterBoxBaselinePosition 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' centerBox [ #baselinePosition 'Data.GI.Base.Attributes.:=' value ]
-- @
setCenterBoxBaselinePosition :: (MonadIO m, IsCenterBox o) => o -> Gtk.Enums.BaselinePosition -> m ()
setCenterBoxBaselinePosition :: o -> BaselinePosition -> m ()
setCenterBoxBaselinePosition 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`.
constructCenterBoxBaselinePosition :: (IsCenterBox o) => Gtk.Enums.BaselinePosition -> IO (GValueConstruct o)
constructCenterBoxBaselinePosition :: BaselinePosition -> IO (GValueConstruct o)
constructCenterBoxBaselinePosition 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 CenterBoxBaselinePositionPropertyInfo
instance AttrInfo CenterBoxBaselinePositionPropertyInfo where
    type AttrAllowedOps CenterBoxBaselinePositionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CenterBoxBaselinePositionPropertyInfo = IsCenterBox
    type AttrSetTypeConstraint CenterBoxBaselinePositionPropertyInfo = (~) Gtk.Enums.BaselinePosition
    type AttrTransferTypeConstraint CenterBoxBaselinePositionPropertyInfo = (~) Gtk.Enums.BaselinePosition
    type AttrTransferType CenterBoxBaselinePositionPropertyInfo = Gtk.Enums.BaselinePosition
    type AttrGetType CenterBoxBaselinePositionPropertyInfo = Gtk.Enums.BaselinePosition
    type AttrLabel CenterBoxBaselinePositionPropertyInfo = "baseline-position"
    type AttrOrigin CenterBoxBaselinePositionPropertyInfo = CenterBox
    attrGet = getCenterBoxBaselinePosition
    attrSet = setCenterBoxBaselinePosition
    attrTransfer _ v = do
        return v
    attrConstruct = constructCenterBoxBaselinePosition
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CenterBox
type instance O.AttributeList CenterBox = CenterBoxAttributeList
type CenterBoxAttributeList = ('[ '("baselinePosition", CenterBoxBaselinePositionPropertyInfo), '("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), '("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), '("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)
centerBoxBaselinePosition :: AttrLabelProxy "baselinePosition"
centerBoxBaselinePosition = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CenterBox = CenterBoxSignalList
type CenterBoxSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("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), '("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 CenterBox::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "CenterBox" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_center_box_new" gtk_center_box_new :: 
    IO (Ptr CenterBox)

-- | Creates a new t'GI.Gtk.Objects.CenterBox.CenterBox'.
centerBoxNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m CenterBox
    -- ^ __Returns:__ the new t'GI.Gtk.Objects.CenterBox.CenterBox'.
centerBoxNew :: m CenterBox
centerBoxNew  = IO CenterBox -> m CenterBox
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CenterBox -> m CenterBox) -> IO CenterBox -> m CenterBox
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterBox
result <- IO (Ptr CenterBox)
gtk_center_box_new
    Text -> Ptr CenterBox -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "centerBoxNew" Ptr CenterBox
result
    CenterBox
result' <- ((ManagedPtr CenterBox -> CenterBox)
-> Ptr CenterBox -> IO CenterBox
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CenterBox -> CenterBox
CenterBox) Ptr CenterBox
result
    CenterBox -> IO CenterBox
forall (m :: * -> *) a. Monad m => a -> m a
return CenterBox
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method CenterBox::get_baseline_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterBox" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterBox" , 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_center_box_get_baseline_position" gtk_center_box_get_baseline_position :: 
    Ptr CenterBox ->                        -- self : TInterface (Name {namespace = "Gtk", name = "CenterBox"})
    IO CUInt

-- | Gets the value set by 'GI.Gtk.Objects.CenterBox.centerBoxSetBaselinePosition'.
centerBoxGetBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterBox a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterBox.CenterBox'
    -> m Gtk.Enums.BaselinePosition
    -- ^ __Returns:__ the baseline position
centerBoxGetBaselinePosition :: a -> m BaselinePosition
centerBoxGetBaselinePosition self :: a
self = 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 CenterBox
self' <- a -> IO (Ptr CenterBox)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr CenterBox -> IO CUInt
gtk_center_box_get_baseline_position Ptr CenterBox
self'
    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
self
    BaselinePosition -> IO BaselinePosition
forall (m :: * -> *) a. Monad m => a -> m a
return BaselinePosition
result'

#if defined(ENABLE_OVERLOADING)
data CenterBoxGetBaselinePositionMethodInfo
instance (signature ~ (m Gtk.Enums.BaselinePosition), MonadIO m, IsCenterBox a) => O.MethodInfo CenterBoxGetBaselinePositionMethodInfo a signature where
    overloadedMethod = centerBoxGetBaselinePosition

#endif

-- method CenterBox::get_center_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterBox" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterBox" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Widget" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_center_box_get_center_widget" gtk_center_box_get_center_widget :: 
    Ptr CenterBox ->                        -- self : TInterface (Name {namespace = "Gtk", name = "CenterBox"})
    IO (Ptr Gtk.Widget.Widget)

-- | Gets the center widget, or 'P.Nothing' if there is none.
centerBoxGetCenterWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterBox a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterBox.CenterBox'
    -> m (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the center widget.
centerBoxGetCenterWidget :: a -> m (Maybe Widget)
centerBoxGetCenterWidget self :: a
self = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterBox
self' <- a -> IO (Ptr CenterBox)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr CenterBox -> IO (Ptr Widget)
gtk_center_box_get_center_widget Ptr CenterBox
self'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Widget -> IO (Maybe Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult

#if defined(ENABLE_OVERLOADING)
data CenterBoxGetCenterWidgetMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsCenterBox a) => O.MethodInfo CenterBoxGetCenterWidgetMethodInfo a signature where
    overloadedMethod = centerBoxGetCenterWidget

#endif

-- method CenterBox::get_end_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterBox" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterBox" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Widget" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_center_box_get_end_widget" gtk_center_box_get_end_widget :: 
    Ptr CenterBox ->                        -- self : TInterface (Name {namespace = "Gtk", name = "CenterBox"})
    IO (Ptr Gtk.Widget.Widget)

-- | Gets the end widget, or 'P.Nothing' if there is none.
centerBoxGetEndWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterBox a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterBox.CenterBox'
    -> m (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the end widget.
centerBoxGetEndWidget :: a -> m (Maybe Widget)
centerBoxGetEndWidget self :: a
self = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterBox
self' <- a -> IO (Ptr CenterBox)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr CenterBox -> IO (Ptr Widget)
gtk_center_box_get_end_widget Ptr CenterBox
self'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Widget -> IO (Maybe Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult

#if defined(ENABLE_OVERLOADING)
data CenterBoxGetEndWidgetMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsCenterBox a) => O.MethodInfo CenterBoxGetEndWidgetMethodInfo a signature where
    overloadedMethod = centerBoxGetEndWidget

#endif

-- method CenterBox::get_start_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterBox" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterBox" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Widget" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_center_box_get_start_widget" gtk_center_box_get_start_widget :: 
    Ptr CenterBox ->                        -- self : TInterface (Name {namespace = "Gtk", name = "CenterBox"})
    IO (Ptr Gtk.Widget.Widget)

-- | Gets the start widget, or 'P.Nothing' if there is none.
centerBoxGetStartWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterBox a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterBox.CenterBox'
    -> m (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the start widget.
centerBoxGetStartWidget :: a -> m (Maybe Widget)
centerBoxGetStartWidget self :: a
self = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterBox
self' <- a -> IO (Ptr CenterBox)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr CenterBox -> IO (Ptr Widget)
gtk_center_box_get_start_widget Ptr CenterBox
self'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Widget -> IO (Maybe Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult

#if defined(ENABLE_OVERLOADING)
data CenterBoxGetStartWidgetMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsCenterBox a) => O.MethodInfo CenterBoxGetStartWidgetMethodInfo a signature where
    overloadedMethod = centerBoxGetStartWidget

#endif

-- method CenterBox::set_baseline_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterBox" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterBox" , 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_center_box_set_baseline_position" gtk_center_box_set_baseline_position :: 
    Ptr CenterBox ->                        -- self : TInterface (Name {namespace = "Gtk", name = "CenterBox"})
    CUInt ->                                -- position : TInterface (Name {namespace = "Gtk", name = "BaselinePosition"})
    IO ()

-- | Sets the baseline position of a center 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.
centerBoxSetBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterBox a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterBox.CenterBox'
    -> Gtk.Enums.BaselinePosition
    -- ^ /@position@/: a t'GI.Gtk.Enums.BaselinePosition'
    -> m ()
centerBoxSetBaselinePosition :: a -> BaselinePosition -> m ()
centerBoxSetBaselinePosition self :: a
self 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 CenterBox
self' <- a -> IO (Ptr CenterBox)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    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 CenterBox -> CUInt -> IO ()
gtk_center_box_set_baseline_position Ptr CenterBox
self' CUInt
position'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CenterBoxSetBaselinePositionMethodInfo
instance (signature ~ (Gtk.Enums.BaselinePosition -> m ()), MonadIO m, IsCenterBox a) => O.MethodInfo CenterBoxSetBaselinePositionMethodInfo a signature where
    overloadedMethod = centerBoxSetBaselinePosition

#endif

-- method CenterBox::set_center_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterBox" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterBox" , 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 = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new center widget, 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_center_box_set_center_widget" gtk_center_box_set_center_widget :: 
    Ptr CenterBox ->                        -- self : TInterface (Name {namespace = "Gtk", name = "CenterBox"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the center widget. To remove the existing center widget, pas 'P.Nothing'.
centerBoxSetCenterWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterBox a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterBox.CenterBox'
    -> Maybe (b)
    -- ^ /@child@/: the new center widget, or 'P.Nothing'
    -> m ()
centerBoxSetCenterWidget :: a -> Maybe b -> m ()
centerBoxSetCenterWidget self :: a
self child :: Maybe b
child = 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 CenterBox
self' <- a -> IO (Ptr CenterBox)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
maybeChild <- case Maybe b
child of
        Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just jChild :: b
jChild -> do
            Ptr Widget
jChild' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jChild
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jChild'
    Ptr CenterBox -> Ptr Widget -> IO ()
gtk_center_box_set_center_widget Ptr CenterBox
self' Ptr Widget
maybeChild
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
child b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CenterBoxSetCenterWidgetMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsCenterBox a, Gtk.Widget.IsWidget b) => O.MethodInfo CenterBoxSetCenterWidgetMethodInfo a signature where
    overloadedMethod = centerBoxSetCenterWidget

#endif

-- method CenterBox::set_end_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterBox" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterBox" , 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 = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new end widget, 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_center_box_set_end_widget" gtk_center_box_set_end_widget :: 
    Ptr CenterBox ->                        -- self : TInterface (Name {namespace = "Gtk", name = "CenterBox"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the end widget. To remove the existing end widget, pass 'P.Nothing'.
centerBoxSetEndWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterBox a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterBox.CenterBox'
    -> Maybe (b)
    -- ^ /@child@/: the new end widget, or 'P.Nothing'
    -> m ()
centerBoxSetEndWidget :: a -> Maybe b -> m ()
centerBoxSetEndWidget self :: a
self child :: Maybe b
child = 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 CenterBox
self' <- a -> IO (Ptr CenterBox)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
maybeChild <- case Maybe b
child of
        Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just jChild :: b
jChild -> do
            Ptr Widget
jChild' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jChild
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jChild'
    Ptr CenterBox -> Ptr Widget -> IO ()
gtk_center_box_set_end_widget Ptr CenterBox
self' Ptr Widget
maybeChild
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
child b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CenterBoxSetEndWidgetMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsCenterBox a, Gtk.Widget.IsWidget b) => O.MethodInfo CenterBoxSetEndWidgetMethodInfo a signature where
    overloadedMethod = centerBoxSetEndWidget

#endif

-- method CenterBox::set_start_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterBox" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterBox" , 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 = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new start widget, 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_center_box_set_start_widget" gtk_center_box_set_start_widget :: 
    Ptr CenterBox ->                        -- self : TInterface (Name {namespace = "Gtk", name = "CenterBox"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the start widget. To remove the existing start widget, pass 'P.Nothing'.
centerBoxSetStartWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterBox a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterBox.CenterBox'
    -> Maybe (b)
    -- ^ /@child@/: the new start widget, or 'P.Nothing'
    -> m ()
centerBoxSetStartWidget :: a -> Maybe b -> m ()
centerBoxSetStartWidget self :: a
self child :: Maybe b
child = 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 CenterBox
self' <- a -> IO (Ptr CenterBox)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
maybeChild <- case Maybe b
child of
        Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just jChild :: b
jChild -> do
            Ptr Widget
jChild' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jChild
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jChild'
    Ptr CenterBox -> Ptr Widget -> IO ()
gtk_center_box_set_start_widget Ptr CenterBox
self' Ptr Widget
maybeChild
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
child b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CenterBoxSetStartWidgetMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsCenterBox a, Gtk.Widget.IsWidget b) => O.MethodInfo CenterBoxSetStartWidgetMethodInfo a signature where
    overloadedMethod = centerBoxSetStartWidget

#endif