{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gtk.Objects.CenterLayout.CenterLayout' is a layout manager that manages up to three children.
-- The start widget is allocated at the start of the layout (left in LRT
-- layouts and right in RTL ones), and the end widget at the end.
-- 
-- The center widget is centered regarding the full width of the layout\'s.

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

module GI.Gtk.Objects.CenterLayout
    ( 

-- * Exported types
    CenterLayout(..)                        ,
    IsCenterLayout                          ,
    toCenterLayout                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveCenterLayoutMethod               ,
#endif


-- ** getBaselinePosition #method:getBaselinePosition#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutGetBaselinePositionMethodInfo,
#endif
    centerLayoutGetBaselinePosition         ,


-- ** getCenterWidget #method:getCenterWidget#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutGetCenterWidgetMethodInfo   ,
#endif
    centerLayoutGetCenterWidget             ,


-- ** getEndWidget #method:getEndWidget#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutGetEndWidgetMethodInfo      ,
#endif
    centerLayoutGetEndWidget                ,


-- ** getOrientation #method:getOrientation#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutGetOrientationMethodInfo    ,
#endif
    centerLayoutGetOrientation              ,


-- ** getStartWidget #method:getStartWidget#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutGetStartWidgetMethodInfo    ,
#endif
    centerLayoutGetStartWidget              ,


-- ** new #method:new#

    centerLayoutNew                         ,


-- ** setBaselinePosition #method:setBaselinePosition#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutSetBaselinePositionMethodInfo,
#endif
    centerLayoutSetBaselinePosition         ,


-- ** setCenterWidget #method:setCenterWidget#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutSetCenterWidgetMethodInfo   ,
#endif
    centerLayoutSetCenterWidget             ,


-- ** setEndWidget #method:setEndWidget#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutSetEndWidgetMethodInfo      ,
#endif
    centerLayoutSetEndWidget                ,


-- ** setOrientation #method:setOrientation#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutSetOrientationMethodInfo    ,
#endif
    centerLayoutSetOrientation              ,


-- ** setStartWidget #method:setStartWidget#

#if defined(ENABLE_OVERLOADING)
    CenterLayoutSetStartWidgetMethodInfo    ,
#endif
    centerLayoutSetStartWidget              ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_center_layout_get_type"
    c_gtk_center_layout_get_type :: IO B.Types.GType

instance B.Types.TypedObject CenterLayout where
    glibType :: IO GType
glibType = IO GType
c_gtk_center_layout_get_type

instance B.Types.GObject CenterLayout

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

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

instance O.HasParentTypes CenterLayout
type instance O.ParentTypes CenterLayout = '[Gtk.LayoutManager.LayoutManager, GObject.Object.Object]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveCenterLayoutMethod (t :: Symbol) (o :: *) :: * where
    ResolveCenterLayoutMethod "allocate" o = Gtk.LayoutManager.LayoutManagerAllocateMethodInfo
    ResolveCenterLayoutMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCenterLayoutMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCenterLayoutMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCenterLayoutMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCenterLayoutMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCenterLayoutMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCenterLayoutMethod "layoutChanged" o = Gtk.LayoutManager.LayoutManagerLayoutChangedMethodInfo
    ResolveCenterLayoutMethod "measure" o = Gtk.LayoutManager.LayoutManagerMeasureMethodInfo
    ResolveCenterLayoutMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCenterLayoutMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCenterLayoutMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCenterLayoutMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCenterLayoutMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCenterLayoutMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCenterLayoutMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCenterLayoutMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCenterLayoutMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCenterLayoutMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCenterLayoutMethod "getBaselinePosition" o = CenterLayoutGetBaselinePositionMethodInfo
    ResolveCenterLayoutMethod "getCenterWidget" o = CenterLayoutGetCenterWidgetMethodInfo
    ResolveCenterLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCenterLayoutMethod "getEndWidget" o = CenterLayoutGetEndWidgetMethodInfo
    ResolveCenterLayoutMethod "getLayoutChild" o = Gtk.LayoutManager.LayoutManagerGetLayoutChildMethodInfo
    ResolveCenterLayoutMethod "getOrientation" o = CenterLayoutGetOrientationMethodInfo
    ResolveCenterLayoutMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCenterLayoutMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCenterLayoutMethod "getRequestMode" o = Gtk.LayoutManager.LayoutManagerGetRequestModeMethodInfo
    ResolveCenterLayoutMethod "getStartWidget" o = CenterLayoutGetStartWidgetMethodInfo
    ResolveCenterLayoutMethod "getWidget" o = Gtk.LayoutManager.LayoutManagerGetWidgetMethodInfo
    ResolveCenterLayoutMethod "setBaselinePosition" o = CenterLayoutSetBaselinePositionMethodInfo
    ResolveCenterLayoutMethod "setCenterWidget" o = CenterLayoutSetCenterWidgetMethodInfo
    ResolveCenterLayoutMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCenterLayoutMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCenterLayoutMethod "setEndWidget" o = CenterLayoutSetEndWidgetMethodInfo
    ResolveCenterLayoutMethod "setOrientation" o = CenterLayoutSetOrientationMethodInfo
    ResolveCenterLayoutMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCenterLayoutMethod "setStartWidget" o = CenterLayoutSetStartWidgetMethodInfo
    ResolveCenterLayoutMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveCenterLayoutMethod t CenterLayout, O.MethodInfo info CenterLayout p) => OL.IsLabel t (CenterLayout -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CenterLayout
type instance O.AttributeList CenterLayout = CenterLayoutAttributeList
type CenterLayoutAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CenterLayout = CenterLayoutSignalList
type CenterLayoutSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_center_layout_new" gtk_center_layout_new :: 
    IO (Ptr CenterLayout)

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

#if defined(ENABLE_OVERLOADING)
#endif

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

-- | Returns the baseline position of the layout.
centerLayoutGetBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> m Gtk.Enums.BaselinePosition
    -- ^ __Returns:__ The current baseline position of /@self@/.
centerLayoutGetBaselinePosition :: a -> m BaselinePosition
centerLayoutGetBaselinePosition 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 CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr CenterLayout -> IO CUInt
gtk_center_layout_get_baseline_position Ptr CenterLayout
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 CenterLayoutGetBaselinePositionMethodInfo
instance (signature ~ (m Gtk.Enums.BaselinePosition), MonadIO m, IsCenterLayout a) => O.MethodInfo CenterLayoutGetBaselinePositionMethodInfo a signature where
    overloadedMethod = centerLayoutGetBaselinePosition

#endif

-- method CenterLayout::get_center_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterLayout" , 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_layout_get_center_widget" gtk_center_layout_get_center_widget :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    IO (Ptr Gtk.Widget.Widget)

-- | Returns the center widget of the layout.
centerLayoutGetCenterWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ the current center widget of /@self@/
centerLayoutGetCenterWidget :: a -> m Widget
centerLayoutGetCenterWidget a
self = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr CenterLayout -> IO (Ptr Widget)
gtk_center_layout_get_center_widget Ptr CenterLayout
self'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"centerLayoutGetCenterWidget" Ptr Widget
result
    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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data CenterLayoutGetCenterWidgetMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsCenterLayout a) => O.MethodInfo CenterLayoutGetCenterWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutGetCenterWidget

#endif

-- method CenterLayout::get_end_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterLayout" , 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_layout_get_end_widget" gtk_center_layout_get_end_widget :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    IO (Ptr Gtk.Widget.Widget)

-- | Returns the end widget of the layout.
centerLayoutGetEndWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ the current end widget of /@self@/
centerLayoutGetEndWidget :: a -> m Widget
centerLayoutGetEndWidget a
self = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr CenterLayout -> IO (Ptr Widget)
gtk_center_layout_get_end_widget Ptr CenterLayout
self'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"centerLayoutGetEndWidget" Ptr Widget
result
    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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data CenterLayoutGetEndWidgetMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsCenterLayout a) => O.MethodInfo CenterLayoutGetEndWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutGetEndWidget

#endif

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

foreign import ccall "gtk_center_layout_get_orientation" gtk_center_layout_get_orientation :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    IO CUInt

-- | Gets the current orienration of the layout manager.
centerLayoutGetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> m Gtk.Enums.Orientation
    -- ^ __Returns:__ The current orientation of /@self@/
centerLayoutGetOrientation :: a -> m Orientation
centerLayoutGetOrientation a
self = IO Orientation -> m Orientation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Orientation -> m Orientation)
-> IO Orientation -> m Orientation
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr CenterLayout -> IO CUInt
gtk_center_layout_get_orientation Ptr CenterLayout
self'
    let result' :: Orientation
result' = (Int -> Orientation
forall a. Enum a => Int -> a
toEnum (Int -> Orientation) -> (CUInt -> Int) -> CUInt -> Orientation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Orientation -> IO Orientation
forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
result'

#if defined(ENABLE_OVERLOADING)
data CenterLayoutGetOrientationMethodInfo
instance (signature ~ (m Gtk.Enums.Orientation), MonadIO m, IsCenterLayout a) => O.MethodInfo CenterLayoutGetOrientationMethodInfo a signature where
    overloadedMethod = centerLayoutGetOrientation

#endif

-- method CenterLayout::get_start_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterLayout" , 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_layout_get_start_widget" gtk_center_layout_get_start_widget :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    IO (Ptr Gtk.Widget.Widget)

-- | Returns the start widget fo the layout.
centerLayoutGetStartWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ The current start widget of /@self@/
centerLayoutGetStartWidget :: a -> m Widget
centerLayoutGetStartWidget a
self = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr CenterLayout -> IO (Ptr Widget)
gtk_center_layout_get_start_widget Ptr CenterLayout
self'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"centerLayoutGetStartWidget" Ptr Widget
result
    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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data CenterLayoutGetStartWidgetMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsCenterLayout a) => O.MethodInfo CenterLayoutGetStartWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutGetStartWidget

#endif

-- method CenterLayout::set_baseline_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "baseline_position"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BaselinePosition" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new baseline position"
--                 , 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_layout_set_baseline_position" gtk_center_layout_set_baseline_position :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    CUInt ->                                -- baseline_position : TInterface (Name {namespace = "Gtk", name = "BaselinePosition"})
    IO ()

-- | Sets the new baseline position of /@self@/
centerLayoutSetBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> Gtk.Enums.BaselinePosition
    -- ^ /@baselinePosition@/: the new baseline position
    -> m ()
centerLayoutSetBaselinePosition :: a -> BaselinePosition -> m ()
centerLayoutSetBaselinePosition a
self BaselinePosition
baselinePosition = 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 CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let baselinePosition' :: CUInt
baselinePosition' = (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
baselinePosition
    Ptr CenterLayout -> CUInt -> IO ()
gtk_center_layout_set_baseline_position Ptr CenterLayout
self' CUInt
baselinePosition'
    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 CenterLayoutSetBaselinePositionMethodInfo
instance (signature ~ (Gtk.Enums.BaselinePosition -> m ()), MonadIO m, IsCenterLayout a) => O.MethodInfo CenterLayoutSetBaselinePositionMethodInfo a signature where
    overloadedMethod = centerLayoutSetBaselinePosition

#endif

-- method CenterLayout::set_center_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new center widget"
--                 , 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_layout_set_center_widget" gtk_center_layout_set_center_widget :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the new center widget of /@self@/
centerLayoutSetCenterWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> b
    -- ^ /@widget@/: the new center widget
    -> m ()
centerLayoutSetCenterWidget :: a -> b -> m ()
centerLayoutSetCenterWidget a
self b
widget = 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 CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr CenterLayout -> Ptr Widget -> IO ()
gtk_center_layout_set_center_widget Ptr CenterLayout
self' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CenterLayoutSetCenterWidgetMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) => O.MethodInfo CenterLayoutSetCenterWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutSetCenterWidget

#endif

-- method CenterLayout::set_end_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new end widget" , 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_layout_set_end_widget" gtk_center_layout_set_end_widget :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the new end widget of /@self@/
centerLayoutSetEndWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> b
    -- ^ /@widget@/: the new end widget
    -> m ()
centerLayoutSetEndWidget :: a -> b -> m ()
centerLayoutSetEndWidget a
self b
widget = 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 CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr CenterLayout -> Ptr Widget -> IO ()
gtk_center_layout_set_end_widget Ptr CenterLayout
self' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CenterLayoutSetEndWidgetMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) => O.MethodInfo CenterLayoutSetEndWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutSetEndWidget

#endif

-- method CenterLayout::set_orientation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "orientation"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Orientation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new orientation"
--                 , 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_layout_set_orientation" gtk_center_layout_set_orientation :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    CUInt ->                                -- orientation : TInterface (Name {namespace = "Gtk", name = "Orientation"})
    IO ()

-- | Sets the orientation of /@self@/.
centerLayoutSetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> Gtk.Enums.Orientation
    -- ^ /@orientation@/: the new orientation
    -> m ()
centerLayoutSetOrientation :: a -> Orientation -> m ()
centerLayoutSetOrientation a
self Orientation
orientation = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    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 CenterLayout -> CUInt -> IO ()
gtk_center_layout_set_orientation Ptr CenterLayout
self' CUInt
orientation'
    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 CenterLayoutSetOrientationMethodInfo
instance (signature ~ (Gtk.Enums.Orientation -> m ()), MonadIO m, IsCenterLayout a) => O.MethodInfo CenterLayoutSetOrientationMethodInfo a signature where
    overloadedMethod = centerLayoutSetOrientation

#endif

-- method CenterLayout::set_start_widget
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "CenterLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkCenterLayout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "widget"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new start widget"
--                 , 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_layout_set_start_widget" gtk_center_layout_set_start_widget :: 
    Ptr CenterLayout ->                     -- self : TInterface (Name {namespace = "Gtk", name = "CenterLayout"})
    Ptr Gtk.Widget.Widget ->                -- widget : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the new start widget of /@self@/.
centerLayoutSetStartWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> b
    -- ^ /@widget@/: the new start widget
    -> m ()
centerLayoutSetStartWidget :: a -> b -> m ()
centerLayoutSetStartWidget a
self b
widget = 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 CenterLayout
self' <- a -> IO (Ptr CenterLayout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
    Ptr CenterLayout -> Ptr Widget -> IO ()
gtk_center_layout_set_start_widget Ptr CenterLayout
self' Ptr Widget
widget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CenterLayoutSetStartWidgetMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) => O.MethodInfo CenterLayoutSetStartWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutSetStartWidget

#endif