{-# 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
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [allocate]("GI.Gtk.Objects.LayoutManager#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [layoutChanged]("GI.Gtk.Objects.LayoutManager#g:method:layoutChanged"), [measure]("GI.Gtk.Objects.LayoutManager#g:method:measure"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBaselinePosition]("GI.Gtk.Objects.CenterLayout#g:method:getBaselinePosition"), [getCenterWidget]("GI.Gtk.Objects.CenterLayout#g:method:getCenterWidget"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getEndWidget]("GI.Gtk.Objects.CenterLayout#g:method:getEndWidget"), [getLayoutChild]("GI.Gtk.Objects.LayoutManager#g:method:getLayoutChild"), [getOrientation]("GI.Gtk.Objects.CenterLayout#g:method:getOrientation"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRequestMode]("GI.Gtk.Objects.LayoutManager#g:method:getRequestMode"), [getStartWidget]("GI.Gtk.Objects.CenterLayout#g:method:getStartWidget"), [getWidget]("GI.Gtk.Objects.LayoutManager#g:method:getWidget").
-- 
-- ==== Setters
-- [setBaselinePosition]("GI.Gtk.Objects.CenterLayout#g:method:setBaselinePosition"), [setCenterWidget]("GI.Gtk.Objects.CenterLayout#g:method:setCenterWidget"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setEndWidget]("GI.Gtk.Objects.CenterLayout#g:method:setEndWidget"), [setOrientation]("GI.Gtk.Objects.CenterLayout#g:method:setOrientation"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setStartWidget]("GI.Gtk.Objects.CenterLayout#g:method:setStartWidget").

#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 GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.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

-- | 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 :: (MIO.MonadIO m, IsCenterLayout o) => o -> m CenterLayout
toCenterLayout :: forall (m :: * -> *) o.
(MonadIO m, IsCenterLayout o) =>
o -> m CenterLayout
toCenterLayout = IO CenterLayout -> m CenterLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr CenterLayout -> CenterLayout
CenterLayout

-- | Convert 'CenterLayout' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe CenterLayout) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_center_layout_get_type
    gvalueSet_ :: Ptr GValue -> Maybe CenterLayout -> IO ()
gvalueSet_ Ptr GValue
gv Maybe CenterLayout
P.Nothing = Ptr GValue -> Ptr CenterLayout -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr CenterLayout
forall a. Ptr a
FP.nullPtr :: FP.Ptr CenterLayout)
    gvalueSet_ Ptr GValue
gv (P.Just CenterLayout
obj) = CenterLayout -> (Ptr CenterLayout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CenterLayout
obj (Ptr GValue -> Ptr CenterLayout -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe CenterLayout)
gvalueGet_ Ptr GValue
gv = do
        Ptr CenterLayout
ptr <- Ptr GValue -> IO (Ptr CenterLayout)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr CenterLayout)
        if Ptr CenterLayout
ptr Ptr CenterLayout -> Ptr CenterLayout -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CenterLayout
forall a. Ptr a
FP.nullPtr
        then CenterLayout -> Maybe CenterLayout
forall a. a -> Maybe a
P.Just (CenterLayout -> Maybe CenterLayout)
-> IO CenterLayout -> IO (Maybe CenterLayout)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe CenterLayout -> IO (Maybe CenterLayout)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CenterLayout
forall a. Maybe a
P.Nothing
        
    

#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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveCenterLayoutMethod t CenterLayout, O.OverloadedMethod info CenterLayout p, R.HasField t CenterLayout p) => R.HasField t CenterLayout p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveCenterLayoutMethod t CenterLayout, O.OverloadedMethodInfo info CenterLayout) => OL.IsLabel t (O.MethodProxy info CenterLayout) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#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 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCenterLayout a) =>
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.OverloadedMethod CenterLayoutGetBaselinePositionMethodInfo a signature where
    overloadedMethod = centerLayoutGetBaselinePosition

instance O.OverloadedMethodInfo CenterLayoutGetBaselinePositionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutGetBaselinePosition",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the current center widget of /@self@/
centerLayoutGetCenterWidget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCenterLayout a) =>
a -> m (Maybe Widget)
centerLayoutGetCenterWidget 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 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'
    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
$ \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 CenterLayoutGetCenterWidgetMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsCenterLayout a) => O.OverloadedMethod CenterLayoutGetCenterWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutGetCenterWidget

instance O.OverloadedMethodInfo CenterLayoutGetCenterWidgetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutGetCenterWidget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the current end widget of /@self@/
centerLayoutGetEndWidget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCenterLayout a) =>
a -> m (Maybe Widget)
centerLayoutGetEndWidget 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 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'
    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
$ \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 CenterLayoutGetEndWidgetMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsCenterLayout a) => O.OverloadedMethod CenterLayoutGetEndWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutGetEndWidget

instance O.OverloadedMethodInfo CenterLayoutGetEndWidgetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutGetEndWidget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCenterLayout a) =>
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.OverloadedMethod CenterLayoutGetOrientationMethodInfo a signature where
    overloadedMethod = centerLayoutGetOrientation

instance O.OverloadedMethodInfo CenterLayoutGetOrientationMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutGetOrientation",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ The current start widget of /@self@/
centerLayoutGetStartWidget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCenterLayout a) =>
a -> m (Maybe Widget)
centerLayoutGetStartWidget 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 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'
    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
$ \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 CenterLayoutGetStartWidgetMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsCenterLayout a) => O.OverloadedMethod CenterLayoutGetStartWidgetMethodInfo a signature where
    overloadedMethod = centerLayoutGetStartWidget

instance O.OverloadedMethodInfo CenterLayoutGetStartWidgetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutGetStartWidget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCenterLayout a) =>
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.OverloadedMethod CenterLayoutSetBaselinePositionMethodInfo a signature where
    overloadedMethod = centerLayoutSetBaselinePosition

instance O.OverloadedMethodInfo CenterLayoutSetBaselinePositionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutSetBaselinePosition",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 = True
--           , 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@/.
-- 
-- To remove the existing center widget, pass 'P.Nothing'.
centerLayoutSetCenterWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> Maybe (b)
    -- ^ /@widget@/: the new center widget
    -> m ()
centerLayoutSetCenterWidget :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCenterLayout a, IsWidget b) =>
a -> Maybe b -> m ()
centerLayoutSetCenterWidget a
self Maybe 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
maybeWidget <- case Maybe b
widget of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jWidget -> do
            Ptr Widget
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jWidget'
    Ptr CenterLayout -> Ptr Widget -> IO ()
gtk_center_layout_set_center_widget Ptr CenterLayout
self' Ptr Widget
maybeWidget
    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
widget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo CenterLayoutSetCenterWidgetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutSetCenterWidget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 = True
--           , 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@/.
-- 
-- To remove the existing center widget, pass 'P.Nothing'.
centerLayoutSetEndWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> Maybe (b)
    -- ^ /@widget@/: the new end widget
    -> m ()
centerLayoutSetEndWidget :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCenterLayout a, IsWidget b) =>
a -> Maybe b -> m ()
centerLayoutSetEndWidget a
self Maybe 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
maybeWidget <- case Maybe b
widget of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jWidget -> do
            Ptr Widget
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jWidget'
    Ptr CenterLayout -> Ptr Widget -> IO ()
gtk_center_layout_set_end_widget Ptr CenterLayout
self' Ptr Widget
maybeWidget
    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
widget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo CenterLayoutSetEndWidgetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutSetEndWidget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCenterLayout a) =>
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.OverloadedMethod CenterLayoutSetOrientationMethodInfo a signature where
    overloadedMethod = centerLayoutSetOrientation

instance O.OverloadedMethodInfo CenterLayoutSetOrientationMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutSetOrientation",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v: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 = True
--           , 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@/.
-- 
-- To remove the existing start widget, pass 'P.Nothing'.
centerLayoutSetStartWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsCenterLayout a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.CenterLayout.CenterLayout'
    -> Maybe (b)
    -- ^ /@widget@/: the new start widget
    -> m ()
centerLayoutSetStartWidget :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCenterLayout a, IsWidget b) =>
a -> Maybe b -> m ()
centerLayoutSetStartWidget a
self Maybe 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
maybeWidget <- case Maybe b
widget of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jWidget -> do
            Ptr Widget
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jWidget'
    Ptr CenterLayout -> Ptr Widget -> IO ()
gtk_center_layout_set_start_widget Ptr CenterLayout
self' Ptr Widget
maybeWidget
    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
widget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo CenterLayoutSetStartWidgetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.CenterLayout.centerLayoutSetStartWidget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-CenterLayout.html#v:centerLayoutSetStartWidget"
        }


#endif