{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gtk.Objects.Container
    ( 

-- * Exported types
    Container(..)                           ,
    ContainerK                              ,
    toContainer                             ,
    noContainer                             ,


 -- * Methods
-- ** containerAdd
    containerAdd                            ,


-- ** containerCheckResize
    containerCheckResize                    ,


-- ** containerChildGetProperty
    containerChildGetProperty               ,


-- ** containerChildNotify
    containerChildNotify                    ,


-- ** containerChildNotifyByPspec
    containerChildNotifyByPspec             ,


-- ** containerChildSetProperty
    containerChildSetProperty               ,


-- ** containerChildType
    containerChildType                      ,


-- ** containerForall
    containerForall                         ,


-- ** containerForeach
    containerForeach                        ,


-- ** containerGetBorderWidth
    containerGetBorderWidth                 ,


-- ** containerGetChildren
    containerGetChildren                    ,


-- ** containerGetFocusChain
    containerGetFocusChain                  ,


-- ** containerGetFocusChild
    containerGetFocusChild                  ,


-- ** containerGetFocusHadjustment
    containerGetFocusHadjustment            ,


-- ** containerGetFocusVadjustment
    containerGetFocusVadjustment            ,


-- ** containerGetPathForChild
    containerGetPathForChild                ,


-- ** containerGetResizeMode
    containerGetResizeMode                  ,


-- ** containerPropagateDraw
    containerPropagateDraw                  ,


-- ** containerRemove
    containerRemove                         ,


-- ** containerResizeChildren
    containerResizeChildren                 ,


-- ** containerSetBorderWidth
    containerSetBorderWidth                 ,


-- ** containerSetFocusChain
    containerSetFocusChain                  ,


-- ** containerSetFocusChild
    containerSetFocusChild                  ,


-- ** containerSetFocusHadjustment
    containerSetFocusHadjustment            ,


-- ** containerSetFocusVadjustment
    containerSetFocusVadjustment            ,


-- ** containerSetReallocateRedraws
    containerSetReallocateRedraws           ,


-- ** containerSetResizeMode
    containerSetResizeMode                  ,


-- ** containerUnsetFocusChain
    containerUnsetFocusChain                ,




 -- * Properties
-- ** BorderWidth
    ContainerBorderWidthPropertyInfo        ,
    constructContainerBorderWidth           ,
    getContainerBorderWidth                 ,
    setContainerBorderWidth                 ,


-- ** Child
    ContainerChildPropertyInfo              ,
    constructContainerChild                 ,
    setContainerChild                       ,


-- ** ResizeMode
    ContainerResizeModePropertyInfo         ,
    constructContainerResizeMode            ,
    getContainerResizeMode                  ,
    setContainerResizeMode                  ,




 -- * Signals
-- ** Add
    ContainerAddCallback                    ,
    ContainerAddCallbackC                   ,
    ContainerAddSignalInfo                  ,
    afterContainerAdd                       ,
    containerAddCallbackWrapper             ,
    containerAddClosure                     ,
    mkContainerAddCallback                  ,
    noContainerAddCallback                  ,
    onContainerAdd                          ,


-- ** CheckResize
    ContainerCheckResizeCallback            ,
    ContainerCheckResizeCallbackC           ,
    ContainerCheckResizeSignalInfo          ,
    afterContainerCheckResize               ,
    containerCheckResizeCallbackWrapper     ,
    containerCheckResizeClosure             ,
    mkContainerCheckResizeCallback          ,
    noContainerCheckResizeCallback          ,
    onContainerCheckResize                  ,


-- ** Remove
    ContainerRemoveCallback                 ,
    ContainerRemoveCallbackC                ,
    ContainerRemoveSignalInfo               ,
    afterContainerRemove                    ,
    containerRemoveCallbackWrapper          ,
    containerRemoveClosure                  ,
    mkContainerRemoveCallback               ,
    noContainerRemoveCallback               ,
    onContainerRemove                       ,


-- ** SetFocusChild
    ContainerSetFocusChildCallback          ,
    ContainerSetFocusChildCallbackC         ,
    ContainerSetFocusChildSignalInfo        ,
    afterContainerSetFocusChild             ,
    containerSetFocusChildCallbackWrapper   ,
    containerSetFocusChildClosure           ,
    mkContainerSetFocusChildCallback        ,
    noContainerSetFocusChildCallback        ,
    onContainerSetFocusChild                ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.Atk as Atk
import qualified GI.GObject as GObject
import qualified GI.Cairo as Cairo

newtype Container = Container (ForeignPtr Container)
foreign import ccall "gtk_container_get_type"
    c_gtk_container_get_type :: IO GType

type instance ParentTypes Container = ContainerParentTypes
type ContainerParentTypes = '[Widget, GObject.Object, Atk.ImplementorIface, Buildable]

instance GObject Container where
    gobjectIsInitiallyUnowned _ = True
    gobjectType _ = c_gtk_container_get_type
    

class GObject o => ContainerK o
instance (GObject o, IsDescendantOf Container o) => ContainerK o

toContainer :: ContainerK o => o -> IO Container
toContainer = unsafeCastTo Container

noContainer :: Maybe Container
noContainer = Nothing

-- signal Container::add
type ContainerAddCallback =
    Widget ->
    IO ()

noContainerAddCallback :: Maybe ContainerAddCallback
noContainerAddCallback = Nothing

type ContainerAddCallbackC =
    Ptr () ->                               -- object
    Ptr Widget ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkContainerAddCallback :: ContainerAddCallbackC -> IO (FunPtr ContainerAddCallbackC)

containerAddClosure :: ContainerAddCallback -> IO Closure
containerAddClosure cb = newCClosure =<< mkContainerAddCallback wrapped
    where wrapped = containerAddCallbackWrapper cb

containerAddCallbackWrapper ::
    ContainerAddCallback ->
    Ptr () ->
    Ptr Widget ->
    Ptr () ->
    IO ()
containerAddCallbackWrapper _cb _ object _ = do
    object' <- (newObject Widget) object
    _cb  object'

onContainerAdd :: (GObject a, MonadIO m) => a -> ContainerAddCallback -> m SignalHandlerId
onContainerAdd obj cb = liftIO $ connectContainerAdd obj cb SignalConnectBefore
afterContainerAdd :: (GObject a, MonadIO m) => a -> ContainerAddCallback -> m SignalHandlerId
afterContainerAdd obj cb = connectContainerAdd obj cb SignalConnectAfter

connectContainerAdd :: (GObject a, MonadIO m) =>
                       a -> ContainerAddCallback -> SignalConnectMode -> m SignalHandlerId
connectContainerAdd obj cb after = liftIO $ do
    cb' <- mkContainerAddCallback (containerAddCallbackWrapper cb)
    connectSignalFunPtr obj "add" cb' after

-- signal Container::check-resize
type ContainerCheckResizeCallback =
    IO ()

noContainerCheckResizeCallback :: Maybe ContainerCheckResizeCallback
noContainerCheckResizeCallback = Nothing

type ContainerCheckResizeCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkContainerCheckResizeCallback :: ContainerCheckResizeCallbackC -> IO (FunPtr ContainerCheckResizeCallbackC)

containerCheckResizeClosure :: ContainerCheckResizeCallback -> IO Closure
containerCheckResizeClosure cb = newCClosure =<< mkContainerCheckResizeCallback wrapped
    where wrapped = containerCheckResizeCallbackWrapper cb

containerCheckResizeCallbackWrapper ::
    ContainerCheckResizeCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
containerCheckResizeCallbackWrapper _cb _ _ = do
    _cb 

onContainerCheckResize :: (GObject a, MonadIO m) => a -> ContainerCheckResizeCallback -> m SignalHandlerId
onContainerCheckResize obj cb = liftIO $ connectContainerCheckResize obj cb SignalConnectBefore
afterContainerCheckResize :: (GObject a, MonadIO m) => a -> ContainerCheckResizeCallback -> m SignalHandlerId
afterContainerCheckResize obj cb = connectContainerCheckResize obj cb SignalConnectAfter

connectContainerCheckResize :: (GObject a, MonadIO m) =>
                               a -> ContainerCheckResizeCallback -> SignalConnectMode -> m SignalHandlerId
connectContainerCheckResize obj cb after = liftIO $ do
    cb' <- mkContainerCheckResizeCallback (containerCheckResizeCallbackWrapper cb)
    connectSignalFunPtr obj "check-resize" cb' after

-- signal Container::remove
type ContainerRemoveCallback =
    Widget ->
    IO ()

noContainerRemoveCallback :: Maybe ContainerRemoveCallback
noContainerRemoveCallback = Nothing

type ContainerRemoveCallbackC =
    Ptr () ->                               -- object
    Ptr Widget ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkContainerRemoveCallback :: ContainerRemoveCallbackC -> IO (FunPtr ContainerRemoveCallbackC)

containerRemoveClosure :: ContainerRemoveCallback -> IO Closure
containerRemoveClosure cb = newCClosure =<< mkContainerRemoveCallback wrapped
    where wrapped = containerRemoveCallbackWrapper cb

containerRemoveCallbackWrapper ::
    ContainerRemoveCallback ->
    Ptr () ->
    Ptr Widget ->
    Ptr () ->
    IO ()
containerRemoveCallbackWrapper _cb _ object _ = do
    object' <- (newObject Widget) object
    _cb  object'

onContainerRemove :: (GObject a, MonadIO m) => a -> ContainerRemoveCallback -> m SignalHandlerId
onContainerRemove obj cb = liftIO $ connectContainerRemove obj cb SignalConnectBefore
afterContainerRemove :: (GObject a, MonadIO m) => a -> ContainerRemoveCallback -> m SignalHandlerId
afterContainerRemove obj cb = connectContainerRemove obj cb SignalConnectAfter

connectContainerRemove :: (GObject a, MonadIO m) =>
                          a -> ContainerRemoveCallback -> SignalConnectMode -> m SignalHandlerId
connectContainerRemove obj cb after = liftIO $ do
    cb' <- mkContainerRemoveCallback (containerRemoveCallbackWrapper cb)
    connectSignalFunPtr obj "remove" cb' after

-- signal Container::set-focus-child
type ContainerSetFocusChildCallback =
    Widget ->
    IO ()

noContainerSetFocusChildCallback :: Maybe ContainerSetFocusChildCallback
noContainerSetFocusChildCallback = Nothing

type ContainerSetFocusChildCallbackC =
    Ptr () ->                               -- object
    Ptr Widget ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkContainerSetFocusChildCallback :: ContainerSetFocusChildCallbackC -> IO (FunPtr ContainerSetFocusChildCallbackC)

containerSetFocusChildClosure :: ContainerSetFocusChildCallback -> IO Closure
containerSetFocusChildClosure cb = newCClosure =<< mkContainerSetFocusChildCallback wrapped
    where wrapped = containerSetFocusChildCallbackWrapper cb

containerSetFocusChildCallbackWrapper ::
    ContainerSetFocusChildCallback ->
    Ptr () ->
    Ptr Widget ->
    Ptr () ->
    IO ()
containerSetFocusChildCallbackWrapper _cb _ object _ = do
    object' <- (newObject Widget) object
    _cb  object'

onContainerSetFocusChild :: (GObject a, MonadIO m) => a -> ContainerSetFocusChildCallback -> m SignalHandlerId
onContainerSetFocusChild obj cb = liftIO $ connectContainerSetFocusChild obj cb SignalConnectBefore
afterContainerSetFocusChild :: (GObject a, MonadIO m) => a -> ContainerSetFocusChildCallback -> m SignalHandlerId
afterContainerSetFocusChild obj cb = connectContainerSetFocusChild obj cb SignalConnectAfter

connectContainerSetFocusChild :: (GObject a, MonadIO m) =>
                                 a -> ContainerSetFocusChildCallback -> SignalConnectMode -> m SignalHandlerId
connectContainerSetFocusChild obj cb after = liftIO $ do
    cb' <- mkContainerSetFocusChildCallback (containerSetFocusChildCallbackWrapper cb)
    connectSignalFunPtr obj "set-focus-child" cb' after

-- VVV Prop "border-width"
   -- Type: TBasicType TUInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getContainerBorderWidth :: (MonadIO m, ContainerK o) => o -> m Word32
getContainerBorderWidth obj = liftIO $ getObjectPropertyCUInt obj "border-width"

setContainerBorderWidth :: (MonadIO m, ContainerK o) => o -> Word32 -> m ()
setContainerBorderWidth obj val = liftIO $ setObjectPropertyCUInt obj "border-width" val

constructContainerBorderWidth :: Word32 -> IO ([Char], GValue)
constructContainerBorderWidth val = constructObjectPropertyCUInt "border-width" val

data ContainerBorderWidthPropertyInfo
instance AttrInfo ContainerBorderWidthPropertyInfo where
    type AttrAllowedOps ContainerBorderWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ContainerBorderWidthPropertyInfo = (~) Word32
    type AttrBaseTypeConstraint ContainerBorderWidthPropertyInfo = ContainerK
    type AttrGetType ContainerBorderWidthPropertyInfo = Word32
    type AttrLabel ContainerBorderWidthPropertyInfo = "Container::border-width"
    attrGet _ = getContainerBorderWidth
    attrSet _ = setContainerBorderWidth
    attrConstruct _ = constructContainerBorderWidth

-- VVV Prop "child"
   -- Type: TInterface "Gtk" "Widget"
   -- Flags: [PropertyWritable]

setContainerChild :: (MonadIO m, ContainerK o, WidgetK a) => o -> a -> m ()
setContainerChild obj val = liftIO $ setObjectPropertyObject obj "child" val

constructContainerChild :: (WidgetK a) => a -> IO ([Char], GValue)
constructContainerChild val = constructObjectPropertyObject "child" val

data ContainerChildPropertyInfo
instance AttrInfo ContainerChildPropertyInfo where
    type AttrAllowedOps ContainerChildPropertyInfo = '[ 'AttrSet, 'AttrConstruct]
    type AttrSetTypeConstraint ContainerChildPropertyInfo = WidgetK
    type AttrBaseTypeConstraint ContainerChildPropertyInfo = ContainerK
    type AttrGetType ContainerChildPropertyInfo = ()
    type AttrLabel ContainerChildPropertyInfo = "Container::child"
    attrGet _ = undefined
    attrSet _ = setContainerChild
    attrConstruct _ = constructContainerChild

-- VVV Prop "resize-mode"
   -- Type: TInterface "Gtk" "ResizeMode"
   -- Flags: [PropertyReadable,PropertyWritable]

getContainerResizeMode :: (MonadIO m, ContainerK o) => o -> m ResizeMode
getContainerResizeMode obj = liftIO $ getObjectPropertyEnum obj "resize-mode"

setContainerResizeMode :: (MonadIO m, ContainerK o) => o -> ResizeMode -> m ()
setContainerResizeMode obj val = liftIO $ setObjectPropertyEnum obj "resize-mode" val

constructContainerResizeMode :: ResizeMode -> IO ([Char], GValue)
constructContainerResizeMode val = constructObjectPropertyEnum "resize-mode" val

data ContainerResizeModePropertyInfo
instance AttrInfo ContainerResizeModePropertyInfo where
    type AttrAllowedOps ContainerResizeModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ContainerResizeModePropertyInfo = (~) ResizeMode
    type AttrBaseTypeConstraint ContainerResizeModePropertyInfo = ContainerK
    type AttrGetType ContainerResizeModePropertyInfo = ResizeMode
    type AttrLabel ContainerResizeModePropertyInfo = "Container::resize-mode"
    attrGet _ = getContainerResizeMode
    attrSet _ = setContainerResizeMode
    attrConstruct _ = constructContainerResizeMode

type instance AttributeList Container = ContainerAttributeList
type ContainerAttributeList = ('[ '("app-paintable", WidgetAppPaintablePropertyInfo), '("border-width", ContainerBorderWidthPropertyInfo), '("can-default", WidgetCanDefaultPropertyInfo), '("can-focus", WidgetCanFocusPropertyInfo), '("child", ContainerChildPropertyInfo), '("composite-child", WidgetCompositeChildPropertyInfo), '("double-buffered", WidgetDoubleBufferedPropertyInfo), '("events", WidgetEventsPropertyInfo), '("expand", WidgetExpandPropertyInfo), '("halign", WidgetHalignPropertyInfo), '("has-default", WidgetHasDefaultPropertyInfo), '("has-focus", WidgetHasFocusPropertyInfo), '("has-tooltip", WidgetHasTooltipPropertyInfo), '("height-request", WidgetHeightRequestPropertyInfo), '("hexpand", WidgetHexpandPropertyInfo), '("hexpand-set", WidgetHexpandSetPropertyInfo), '("is-focus", WidgetIsFocusPropertyInfo), '("margin", WidgetMarginPropertyInfo), '("margin-bottom", WidgetMarginBottomPropertyInfo), '("margin-end", WidgetMarginEndPropertyInfo), '("margin-left", WidgetMarginLeftPropertyInfo), '("margin-right", WidgetMarginRightPropertyInfo), '("margin-start", WidgetMarginStartPropertyInfo), '("margin-top", WidgetMarginTopPropertyInfo), '("name", WidgetNamePropertyInfo), '("no-show-all", WidgetNoShowAllPropertyInfo), '("opacity", WidgetOpacityPropertyInfo), '("parent", WidgetParentPropertyInfo), '("receives-default", WidgetReceivesDefaultPropertyInfo), '("resize-mode", ContainerResizeModePropertyInfo), '("scale-factor", WidgetScaleFactorPropertyInfo), '("sensitive", WidgetSensitivePropertyInfo), '("style", WidgetStylePropertyInfo), '("tooltip-markup", WidgetTooltipMarkupPropertyInfo), '("tooltip-text", WidgetTooltipTextPropertyInfo), '("valign", WidgetValignPropertyInfo), '("vexpand", WidgetVexpandPropertyInfo), '("vexpand-set", WidgetVexpandSetPropertyInfo), '("visible", WidgetVisiblePropertyInfo), '("width-request", WidgetWidthRequestPropertyInfo), '("window", WidgetWindowPropertyInfo)] :: [(Symbol, *)])

data ContainerAddSignalInfo
instance SignalInfo ContainerAddSignalInfo where
    type HaskellCallbackType ContainerAddSignalInfo = ContainerAddCallback
    connectSignal _ = connectContainerAdd

data ContainerCheckResizeSignalInfo
instance SignalInfo ContainerCheckResizeSignalInfo where
    type HaskellCallbackType ContainerCheckResizeSignalInfo = ContainerCheckResizeCallback
    connectSignal _ = connectContainerCheckResize

data ContainerRemoveSignalInfo
instance SignalInfo ContainerRemoveSignalInfo where
    type HaskellCallbackType ContainerRemoveSignalInfo = ContainerRemoveCallback
    connectSignal _ = connectContainerRemove

data ContainerSetFocusChildSignalInfo
instance SignalInfo ContainerSetFocusChildSignalInfo where
    type HaskellCallbackType ContainerSetFocusChildSignalInfo = ContainerSetFocusChildCallback
    connectSignal _ = connectContainerSetFocusChild

type instance SignalList Container = ContainerSignalList
type ContainerSignalList = ('[ '("accel-closures-changed", WidgetAccelClosuresChangedSignalInfo), '("add", ContainerAddSignalInfo), '("button-press-event", WidgetButtonPressEventSignalInfo), '("button-release-event", WidgetButtonReleaseEventSignalInfo), '("can-activate-accel", WidgetCanActivateAccelSignalInfo), '("check-resize", ContainerCheckResizeSignalInfo), '("child-notify", WidgetChildNotifySignalInfo), '("composited-changed", WidgetCompositedChangedSignalInfo), '("configure-event", WidgetConfigureEventSignalInfo), '("damage-event", WidgetDamageEventSignalInfo), '("delete-event", WidgetDeleteEventSignalInfo), '("destroy", WidgetDestroySignalInfo), '("destroy-event", WidgetDestroyEventSignalInfo), '("direction-changed", WidgetDirectionChangedSignalInfo), '("drag-begin", WidgetDragBeginSignalInfo), '("drag-data-delete", WidgetDragDataDeleteSignalInfo), '("drag-data-get", WidgetDragDataGetSignalInfo), '("drag-data-received", WidgetDragDataReceivedSignalInfo), '("drag-drop", WidgetDragDropSignalInfo), '("drag-end", WidgetDragEndSignalInfo), '("drag-failed", WidgetDragFailedSignalInfo), '("drag-leave", WidgetDragLeaveSignalInfo), '("drag-motion", WidgetDragMotionSignalInfo), '("draw", WidgetDrawSignalInfo), '("enter-notify-event", WidgetEnterNotifyEventSignalInfo), '("event", WidgetEventSignalInfo), '("event-after", WidgetEventAfterSignalInfo), '("focus", WidgetFocusSignalInfo), '("focus-in-event", WidgetFocusInEventSignalInfo), '("focus-out-event", WidgetFocusOutEventSignalInfo), '("grab-broken-event", WidgetGrabBrokenEventSignalInfo), '("grab-focus", WidgetGrabFocusSignalInfo), '("grab-notify", WidgetGrabNotifySignalInfo), '("hide", WidgetHideSignalInfo), '("hierarchy-changed", WidgetHierarchyChangedSignalInfo), '("key-press-event", WidgetKeyPressEventSignalInfo), '("key-release-event", WidgetKeyReleaseEventSignalInfo), '("keynav-failed", WidgetKeynavFailedSignalInfo), '("leave-notify-event", WidgetLeaveNotifyEventSignalInfo), '("map", WidgetMapSignalInfo), '("map-event", WidgetMapEventSignalInfo), '("mnemonic-activate", WidgetMnemonicActivateSignalInfo), '("motion-notify-event", WidgetMotionNotifyEventSignalInfo), '("move-focus", WidgetMoveFocusSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("parent-set", WidgetParentSetSignalInfo), '("popup-menu", WidgetPopupMenuSignalInfo), '("property-notify-event", WidgetPropertyNotifyEventSignalInfo), '("proximity-in-event", WidgetProximityInEventSignalInfo), '("proximity-out-event", WidgetProximityOutEventSignalInfo), '("query-tooltip", WidgetQueryTooltipSignalInfo), '("realize", WidgetRealizeSignalInfo), '("remove", ContainerRemoveSignalInfo), '("screen-changed", WidgetScreenChangedSignalInfo), '("scroll-event", WidgetScrollEventSignalInfo), '("selection-clear-event", WidgetSelectionClearEventSignalInfo), '("selection-get", WidgetSelectionGetSignalInfo), '("selection-notify-event", WidgetSelectionNotifyEventSignalInfo), '("selection-received", WidgetSelectionReceivedSignalInfo), '("selection-request-event", WidgetSelectionRequestEventSignalInfo), '("set-focus-child", ContainerSetFocusChildSignalInfo), '("show", WidgetShowSignalInfo), '("show-help", WidgetShowHelpSignalInfo), '("size-allocate", WidgetSizeAllocateSignalInfo), '("state-changed", WidgetStateChangedSignalInfo), '("state-flags-changed", WidgetStateFlagsChangedSignalInfo), '("style-set", WidgetStyleSetSignalInfo), '("style-updated", WidgetStyleUpdatedSignalInfo), '("touch-event", WidgetTouchEventSignalInfo), '("unmap", WidgetUnmapSignalInfo), '("unmap-event", WidgetUnmapEventSignalInfo), '("unrealize", WidgetUnrealizeSignalInfo), '("visibility-notify-event", WidgetVisibilityNotifyEventSignalInfo), '("window-state-event", WidgetWindowStateEventSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method Container::add
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_add" gtk_container_add :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    IO ()


containerAdd ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- widget
    m ()
containerAdd _obj widget = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let widget' = unsafeManagedPtrCastPtr widget
    gtk_container_add _obj' widget'
    touchManagedPtr _obj
    touchManagedPtr widget
    return ()

-- method Container::check_resize
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_check_resize" gtk_container_check_resize :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO ()


containerCheckResize ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m ()
containerCheckResize _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_container_check_resize _obj'
    touchManagedPtr _obj
    return ()

-- method Container::child_get_property
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "property_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TInterface "GObject" "Value", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "property_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TInterface "GObject" "Value", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_child_get_property" gtk_container_child_get_property :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    CString ->                              -- property_name : TBasicType TUTF8
    Ptr GValue ->                           -- value : TInterface "GObject" "Value"
    IO ()


containerChildGetProperty ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- child
    T.Text ->                               -- property_name
    GValue ->                               -- value
    m ()
containerChildGetProperty _obj child property_name value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    property_name' <- textToCString property_name
    let value' = unsafeManagedPtrGetPtr value
    gtk_container_child_get_property _obj' child' property_name' value'
    touchManagedPtr _obj
    touchManagedPtr child
    touchManagedPtr value
    freeMem property_name'
    return ()

-- method Container::child_notify
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_property", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_property", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_child_notify" gtk_container_child_notify :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    CString ->                              -- child_property : TBasicType TUTF8
    IO ()


containerChildNotify ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- child
    T.Text ->                               -- child_property
    m ()
containerChildNotify _obj child child_property = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    child_property' <- textToCString child_property
    gtk_container_child_notify _obj' child' child_property'
    touchManagedPtr _obj
    touchManagedPtr child
    freeMem child_property'
    return ()

-- method Container::child_notify_by_pspec
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pspec", argType = TParamSpec, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pspec", argType = TParamSpec, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_child_notify_by_pspec" gtk_container_child_notify_by_pspec :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    Ptr GParamSpec ->                       -- pspec : TParamSpec
    IO ()


containerChildNotifyByPspec ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- child
    GParamSpec ->                           -- pspec
    m ()
containerChildNotifyByPspec _obj child pspec = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    let pspec' = unsafeManagedPtrGetPtr pspec
    gtk_container_child_notify_by_pspec _obj' child' pspec'
    touchManagedPtr _obj
    touchManagedPtr child
    return ()

-- method Container::child_set_property
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "property_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TInterface "GObject" "Value", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "property_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TInterface "GObject" "Value", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_child_set_property" gtk_container_child_set_property :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    CString ->                              -- property_name : TBasicType TUTF8
    Ptr GValue ->                           -- value : TInterface "GObject" "Value"
    IO ()


containerChildSetProperty ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- child
    T.Text ->                               -- property_name
    GValue ->                               -- value
    m ()
containerChildSetProperty _obj child property_name value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    property_name' <- textToCString property_name
    let value' = unsafeManagedPtrGetPtr value
    gtk_container_child_set_property _obj' child' property_name' value'
    touchManagedPtr _obj
    touchManagedPtr child
    touchManagedPtr value
    freeMem property_name'
    return ()

-- method Container::child_type
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TGType
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_child_type" gtk_container_child_type :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO CGType


containerChildType ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m GType
containerChildType _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_container_child_type _obj'
    let result' = GType result
    touchManagedPtr _obj
    return result'

-- method Container::forall
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gtk" "Callback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeCall, argClosure = 2, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gtk" "Callback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeCall, argClosure = 2, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_forall" gtk_container_forall :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    FunPtr CallbackC ->                     -- callback : TInterface "Gtk" "Callback"
    Ptr () ->                               -- callback_data : TBasicType TVoid
    IO ()


containerForall ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    Callback ->                             -- callback
    m ()
containerForall _obj callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    callback' <- mkCallback (callbackWrapper Nothing callback)
    let callback_data = nullPtr
    gtk_container_forall _obj' callback' callback_data
    safeFreeFunPtr $ castFunPtrToPtr callback'
    touchManagedPtr _obj
    return ()

-- method Container::foreach
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gtk" "Callback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeCall, argClosure = 2, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gtk" "Callback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeCall, argClosure = 2, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_foreach" gtk_container_foreach :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    FunPtr CallbackC ->                     -- callback : TInterface "Gtk" "Callback"
    Ptr () ->                               -- callback_data : TBasicType TVoid
    IO ()


containerForeach ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    Callback ->                             -- callback
    m ()
containerForeach _obj callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    callback' <- mkCallback (callbackWrapper Nothing callback)
    let callback_data = nullPtr
    gtk_container_foreach _obj' callback' callback_data
    safeFreeFunPtr $ castFunPtrToPtr callback'
    touchManagedPtr _obj
    return ()

-- method Container::get_border_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_get_border_width" gtk_container_get_border_width :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO Word32


containerGetBorderWidth ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m Word32
containerGetBorderWidth _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_container_get_border_width _obj'
    touchManagedPtr _obj
    return result

-- method Container::get_children
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TGList (TInterface "Gtk" "Widget")
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_get_children" gtk_container_get_children :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO (Ptr (GList (Ptr Widget)))


containerGetChildren ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m [Widget]
containerGetChildren _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_container_get_children _obj'
    checkUnexpectedReturnNULL "gtk_container_get_children" result
    result' <- unpackGList result
    result'' <- mapM (newObject Widget) result'
    g_list_free result
    touchManagedPtr _obj
    return result''

-- method Container::get_focus_chain
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "focusable_widgets", argType = TGList (TInterface "Gtk" "Widget"), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferContainer}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_get_focus_chain" gtk_container_get_focus_chain :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr (Ptr (GList (Ptr Widget))) ->       -- focusable_widgets : TGList (TInterface "Gtk" "Widget")
    IO CInt


containerGetFocusChain ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m (Bool,[Widget])
containerGetFocusChain _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    focusable_widgets <- allocMem :: IO (Ptr (Ptr (GList (Ptr Widget))))
    result <- gtk_container_get_focus_chain _obj' focusable_widgets
    let result' = (/= 0) result
    focusable_widgets' <- peek focusable_widgets
    focusable_widgets'' <- unpackGList focusable_widgets'
    focusable_widgets''' <- mapM (newObject Widget) focusable_widgets''
    g_list_free focusable_widgets'
    touchManagedPtr _obj
    freeMem focusable_widgets
    return (result', focusable_widgets''')

-- method Container::get_focus_child
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Widget"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_get_focus_child" gtk_container_get_focus_child :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO (Ptr Widget)


containerGetFocusChild ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m Widget
containerGetFocusChild _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_container_get_focus_child _obj'
    checkUnexpectedReturnNULL "gtk_container_get_focus_child" result
    result' <- (newObject Widget) result
    touchManagedPtr _obj
    return result'

-- method Container::get_focus_hadjustment
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Adjustment"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_get_focus_hadjustment" gtk_container_get_focus_hadjustment :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO (Ptr Adjustment)


containerGetFocusHadjustment ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m Adjustment
containerGetFocusHadjustment _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_container_get_focus_hadjustment _obj'
    checkUnexpectedReturnNULL "gtk_container_get_focus_hadjustment" result
    result' <- (newObject Adjustment) result
    touchManagedPtr _obj
    return result'

-- method Container::get_focus_vadjustment
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "Adjustment"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_get_focus_vadjustment" gtk_container_get_focus_vadjustment :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO (Ptr Adjustment)


containerGetFocusVadjustment ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m Adjustment
containerGetFocusVadjustment _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_container_get_focus_vadjustment _obj'
    checkUnexpectedReturnNULL "gtk_container_get_focus_vadjustment" result
    result' <- (newObject Adjustment) result
    touchManagedPtr _obj
    return result'

-- method Container::get_path_for_child
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "WidgetPath"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_get_path_for_child" gtk_container_get_path_for_child :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    IO (Ptr WidgetPath)


containerGetPathForChild ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- child
    m WidgetPath
containerGetPathForChild _obj child = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    result <- gtk_container_get_path_for_child _obj' child'
    checkUnexpectedReturnNULL "gtk_container_get_path_for_child" result
    result' <- (wrapBoxed WidgetPath) result
    touchManagedPtr _obj
    touchManagedPtr child
    return result'

-- method Container::get_resize_mode
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "ResizeMode"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_get_resize_mode" gtk_container_get_resize_mode :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO CUInt

{-# DEPRECATED containerGetResizeMode ["(Since version 3.12)","Resize modes are deprecated. They aren\8217t necessary","    anymore since frame clocks and might introduce obscure bugs if","    used."]#-}
containerGetResizeMode ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m ResizeMode
containerGetResizeMode _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_container_get_resize_mode _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method Container::propagate_draw
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cr", argType = TInterface "cairo" "Context", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cr", argType = TInterface "cairo" "Context", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_propagate_draw" gtk_container_propagate_draw :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    Ptr Cairo.Context ->                    -- cr : TInterface "cairo" "Context"
    IO ()


containerPropagateDraw ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- child
    Cairo.Context ->                        -- cr
    m ()
containerPropagateDraw _obj child cr = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let child' = unsafeManagedPtrCastPtr child
    let cr' = unsafeManagedPtrGetPtr cr
    gtk_container_propagate_draw _obj' child' cr'
    touchManagedPtr _obj
    touchManagedPtr child
    touchManagedPtr cr
    return ()

-- method Container::remove
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_remove" gtk_container_remove :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    IO ()


containerRemove ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- widget
    m ()
containerRemove _obj widget = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let widget' = unsafeManagedPtrCastPtr widget
    gtk_container_remove _obj' widget'
    touchManagedPtr _obj
    touchManagedPtr widget
    return ()

-- method Container::resize_children
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_resize_children" gtk_container_resize_children :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO ()

{-# DEPRECATED containerResizeChildren ["(Since version 3.10)"]#-}
containerResizeChildren ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m ()
containerResizeChildren _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_container_resize_children _obj'
    touchManagedPtr _obj
    return ()

-- method Container::set_border_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "border_width", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "border_width", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_set_border_width" gtk_container_set_border_width :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Word32 ->                               -- border_width : TBasicType TUInt32
    IO ()


containerSetBorderWidth ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    Word32 ->                               -- border_width
    m ()
containerSetBorderWidth _obj border_width = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_container_set_border_width _obj' border_width
    touchManagedPtr _obj
    return ()

-- method Container::set_focus_chain
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "focusable_widgets", argType = TGList (TInterface "Gtk" "Widget"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "focusable_widgets", argType = TGList (TInterface "Gtk" "Widget"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_set_focus_chain" gtk_container_set_focus_chain :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr (GList (Ptr Widget)) ->             -- focusable_widgets : TGList (TInterface "Gtk" "Widget")
    IO ()


containerSetFocusChain ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    [b] ->                                  -- focusable_widgets
    m ()
containerSetFocusChain _obj focusable_widgets = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let focusable_widgets' = map unsafeManagedPtrCastPtr focusable_widgets
    focusable_widgets'' <- packGList focusable_widgets'
    gtk_container_set_focus_chain _obj' focusable_widgets''
    touchManagedPtr _obj
    mapM_ touchManagedPtr focusable_widgets
    g_list_free focusable_widgets''
    return ()

-- method Container::set_focus_child
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_set_focus_child" gtk_container_set_focus_child :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Widget ->                           -- child : TInterface "Gtk" "Widget"
    IO ()


containerSetFocusChild ::
    (MonadIO m, ContainerK a, WidgetK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- child
    m ()
containerSetFocusChild _obj child = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeChild <- case child of
        Nothing -> return nullPtr
        Just jChild -> do
            let jChild' = unsafeManagedPtrCastPtr jChild
            return jChild'
    gtk_container_set_focus_child _obj' maybeChild
    touchManagedPtr _obj
    whenJust child touchManagedPtr
    return ()

-- method Container::set_focus_hadjustment
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "adjustment", argType = TInterface "Gtk" "Adjustment", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "adjustment", argType = TInterface "Gtk" "Adjustment", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_set_focus_hadjustment" gtk_container_set_focus_hadjustment :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Adjustment ->                       -- adjustment : TInterface "Gtk" "Adjustment"
    IO ()


containerSetFocusHadjustment ::
    (MonadIO m, ContainerK a, AdjustmentK b) =>
    a ->                                    -- _obj
    b ->                                    -- adjustment
    m ()
containerSetFocusHadjustment _obj adjustment = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let adjustment' = unsafeManagedPtrCastPtr adjustment
    gtk_container_set_focus_hadjustment _obj' adjustment'
    touchManagedPtr _obj
    touchManagedPtr adjustment
    return ()

-- method Container::set_focus_vadjustment
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "adjustment", argType = TInterface "Gtk" "Adjustment", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "adjustment", argType = TInterface "Gtk" "Adjustment", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_set_focus_vadjustment" gtk_container_set_focus_vadjustment :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    Ptr Adjustment ->                       -- adjustment : TInterface "Gtk" "Adjustment"
    IO ()


containerSetFocusVadjustment ::
    (MonadIO m, ContainerK a, AdjustmentK b) =>
    a ->                                    -- _obj
    b ->                                    -- adjustment
    m ()
containerSetFocusVadjustment _obj adjustment = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let adjustment' = unsafeManagedPtrCastPtr adjustment
    gtk_container_set_focus_vadjustment _obj' adjustment'
    touchManagedPtr _obj
    touchManagedPtr adjustment
    return ()

-- method Container::set_reallocate_redraws
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "needs_redraws", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "needs_redraws", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_set_reallocate_redraws" gtk_container_set_reallocate_redraws :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    CInt ->                                 -- needs_redraws : TBasicType TBoolean
    IO ()

{-# DEPRECATED containerSetReallocateRedraws ["(Since version 3.14)","Call gtk_widget_queue_draw() in your size_allocate handler."]#-}
containerSetReallocateRedraws ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- needs_redraws
    m ()
containerSetReallocateRedraws _obj needs_redraws = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let needs_redraws' = (fromIntegral . fromEnum) needs_redraws
    gtk_container_set_reallocate_redraws _obj' needs_redraws'
    touchManagedPtr _obj
    return ()

-- method Container::set_resize_mode
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "resize_mode", argType = TInterface "Gtk" "ResizeMode", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "resize_mode", argType = TInterface "Gtk" "ResizeMode", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_set_resize_mode" gtk_container_set_resize_mode :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    CUInt ->                                -- resize_mode : TInterface "Gtk" "ResizeMode"
    IO ()

{-# DEPRECATED containerSetResizeMode ["(Since version 3.12)","Resize modes are deprecated. They aren\8217t necessary","    anymore since frame clocks and might introduce obscure bugs if","    used."]#-}
containerSetResizeMode ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    ResizeMode ->                           -- resize_mode
    m ()
containerSetResizeMode _obj resize_mode = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let resize_mode' = (fromIntegral . fromEnum) resize_mode
    gtk_container_set_resize_mode _obj' resize_mode'
    touchManagedPtr _obj
    return ()

-- method Container::unset_focus_chain
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "Container", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_container_unset_focus_chain" gtk_container_unset_focus_chain :: 
    Ptr Container ->                        -- _obj : TInterface "Gtk" "Container"
    IO ()


containerUnsetFocusChain ::
    (MonadIO m, ContainerK a) =>
    a ->                                    -- _obj
    m ()
containerUnsetFocusChain _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_container_unset_focus_chain _obj'
    touchManagedPtr _obj
    return ()