{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Gtk.Structs.TableChild
    ( 

-- * Exported types
    TableChild(..)                          ,
    newZeroTableChild                       ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveTableChildMethod                 ,
#endif



 -- * Properties


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

    getTableChildBottomAttach               ,
    setTableChildBottomAttach               ,
#if defined(ENABLE_OVERLOADING)
    tableChild_bottomAttach                 ,
#endif


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

    getTableChildLeftAttach                 ,
    setTableChildLeftAttach                 ,
#if defined(ENABLE_OVERLOADING)
    tableChild_leftAttach                   ,
#endif


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

    getTableChildRightAttach                ,
    setTableChildRightAttach                ,
#if defined(ENABLE_OVERLOADING)
    tableChild_rightAttach                  ,
#endif


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

    getTableChildTopAttach                  ,
    setTableChildTopAttach                  ,
#if defined(ENABLE_OVERLOADING)
    tableChild_topAttach                    ,
#endif


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

    clearTableChildWidget                   ,
    getTableChildWidget                     ,
    setTableChildWidget                     ,
#if defined(ENABLE_OVERLOADING)
    tableChild_widget                       ,
#endif


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

    getTableChildXexpand                    ,
    setTableChildXexpand                    ,
#if defined(ENABLE_OVERLOADING)
    tableChild_xexpand                      ,
#endif


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

    getTableChildXfill                      ,
    setTableChildXfill                      ,
#if defined(ENABLE_OVERLOADING)
    tableChild_xfill                        ,
#endif


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

    getTableChildXpadding                   ,
    setTableChildXpadding                   ,
#if defined(ENABLE_OVERLOADING)
    tableChild_xpadding                     ,
#endif


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

    getTableChildXshrink                    ,
    setTableChildXshrink                    ,
#if defined(ENABLE_OVERLOADING)
    tableChild_xshrink                      ,
#endif


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

    getTableChildYexpand                    ,
    setTableChildYexpand                    ,
#if defined(ENABLE_OVERLOADING)
    tableChild_yexpand                      ,
#endif


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

    getTableChildYfill                      ,
    setTableChildYfill                      ,
#if defined(ENABLE_OVERLOADING)
    tableChild_yfill                        ,
#endif


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

    getTableChildYpadding                   ,
    setTableChildYpadding                   ,
#if defined(ENABLE_OVERLOADING)
    tableChild_ypadding                     ,
#endif


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

    getTableChildYshrink                    ,
    setTableChildYshrink                    ,
#if defined(ENABLE_OVERLOADING)
    tableChild_yshrink                      ,
#endif




    ) 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.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.MarkupParser as GLib.MarkupParser
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Enums as Gdk.Enums
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.DragContext as Gdk.DragContext
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Screen as Gdk.Screen
import qualified GI.Gdk.Objects.Visual as Gdk.Visual
import qualified GI.Gdk.Objects.Window as Gdk.Window
import qualified GI.Gdk.Structs.Atom as Gdk.Atom
import qualified GI.Gdk.Structs.Color as Gdk.Color
import qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.ActionMap as Gio.ActionMap
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.Application as Gio.Application
import qualified GI.Gio.Objects.Menu as Gio.Menu
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Objects.AccelGroup as Gtk.AccelGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.Adjustment as Gtk.Adjustment
import {-# SOURCE #-} qualified GI.Gtk.Objects.Application as Gtk.Application
import {-# SOURCE #-} qualified GI.Gtk.Objects.Bin as Gtk.Bin
import {-# SOURCE #-} qualified GI.Gtk.Objects.Builder as Gtk.Builder
import {-# SOURCE #-} qualified GI.Gtk.Objects.Clipboard as Gtk.Clipboard
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.IconFactory as Gtk.IconFactory
import {-# SOURCE #-} qualified GI.Gtk.Objects.RcStyle as Gtk.RcStyle
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Style as Gtk.Style
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleProperties as Gtk.StyleProperties
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextBuffer as Gtk.TextBuffer
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextChildAnchor as Gtk.TextChildAnchor
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextMark as Gtk.TextMark
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextTag as Gtk.TextTag
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextTagTable as Gtk.TextTagTable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
import {-# SOURCE #-} qualified GI.Gtk.Objects.WindowGroup as Gtk.WindowGroup
import {-# SOURCE #-} qualified GI.Gtk.Structs.AccelGroupEntry as Gtk.AccelGroupEntry
import {-# SOURCE #-} qualified GI.Gtk.Structs.AccelKey as Gtk.AccelKey
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.CssSection as Gtk.CssSection
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSet as Gtk.IconSet
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSource as Gtk.IconSource
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import {-# SOURCE #-} qualified GI.Gtk.Structs.SelectionData as Gtk.SelectionData
import {-# SOURCE #-} qualified GI.Gtk.Structs.SettingsValue as Gtk.SettingsValue
import {-# SOURCE #-} qualified GI.Gtk.Structs.SymbolicColor as Gtk.SymbolicColor
import {-# SOURCE #-} qualified GI.Gtk.Structs.TargetEntry as Gtk.TargetEntry
import {-# SOURCE #-} qualified GI.Gtk.Structs.TargetList as Gtk.TargetList
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextAppearance as Gtk.TextAppearance
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextAttributes as Gtk.TextAttributes
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextIter as Gtk.TextIter
import {-# SOURCE #-} qualified GI.Gtk.Structs.WidgetPath as Gtk.WidgetPath
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout
import qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
import qualified GI.Pango.Structs.Language as Pango.Language
import qualified GI.Pango.Structs.TabArray as Pango.TabArray

#else
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

#endif

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

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

instance BoxedPtr TableChild where
    boxedPtrCopy :: TableChild -> IO TableChild
boxedPtrCopy = \TableChild
p -> TableChild -> (Ptr TableChild -> IO TableChild) -> IO TableChild
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TableChild
p (Int -> Ptr TableChild -> IO (Ptr TableChild)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
48 (Ptr TableChild -> IO (Ptr TableChild))
-> (Ptr TableChild -> IO TableChild)
-> Ptr TableChild
-> IO TableChild
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TableChild -> TableChild)
-> Ptr TableChild -> IO TableChild
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr TableChild -> TableChild
TableChild)
    boxedPtrFree :: TableChild -> IO ()
boxedPtrFree = \TableChild
x -> TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr TableChild
x Ptr TableChild -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr TableChild where
    boxedPtrCalloc :: IO (Ptr TableChild)
boxedPtrCalloc = Int -> IO (Ptr TableChild)
forall a. Int -> IO (Ptr a)
callocBytes Int
48


-- | Construct a `TableChild` struct initialized to zero.
newZeroTableChild :: MonadIO m => m TableChild
newZeroTableChild :: forall (m :: * -> *). MonadIO m => m TableChild
newZeroTableChild = IO TableChild -> m TableChild
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TableChild -> m TableChild) -> IO TableChild -> m TableChild
forall a b. (a -> b) -> a -> b
$ IO (Ptr TableChild)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr TableChild)
-> (Ptr TableChild -> IO TableChild) -> IO TableChild
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TableChild -> TableChild)
-> Ptr TableChild -> IO TableChild
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TableChild -> TableChild
TableChild

instance tag ~ 'AttrSet => Constructible TableChild tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr TableChild -> TableChild)
-> [AttrOp TableChild tag] -> m TableChild
new ManagedPtr TableChild -> TableChild
_ [AttrOp TableChild tag]
attrs = do
        TableChild
o <- m TableChild
forall (m :: * -> *). MonadIO m => m TableChild
newZeroTableChild
        TableChild -> [AttrOp TableChild 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TableChild
o [AttrOp TableChild tag]
[AttrOp TableChild 'AttrSet]
attrs
        TableChild -> m TableChild
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return TableChild
o


-- | Get the value of the “@widget@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #widget
-- @
getTableChildWidget :: MonadIO m => TableChild -> m (Maybe Gtk.Widget.Widget)
getTableChildWidget :: forall (m :: * -> *). MonadIO m => TableChild -> m (Maybe Widget)
getTableChildWidget TableChild
s = IO (Maybe Widget) -> m (Maybe Widget)
forall a. IO a -> m a
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
$ TableChild
-> (Ptr TableChild -> IO (Maybe Widget)) -> IO (Maybe Widget)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO (Maybe Widget)) -> IO (Maybe Widget))
-> (Ptr TableChild -> IO (Maybe Widget)) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Widget
val <- Ptr (Ptr Widget) -> IO (Ptr Widget)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr (Ptr Widget)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO (Ptr Gtk.Widget.Widget)
    Maybe Widget
result <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Widget
val ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
val' -> do
        Widget
val'' <- ((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
val'
        Widget -> IO Widget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
val''
    Maybe Widget -> IO (Maybe Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
result

-- | Set the value of the “@widget@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #widget 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildWidget :: MonadIO m => TableChild -> Ptr Gtk.Widget.Widget -> m ()
setTableChildWidget :: forall (m :: * -> *). MonadIO m => TableChild -> Ptr Widget -> m ()
setTableChildWidget TableChild
s Ptr Widget
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr (Ptr Widget) -> Ptr Widget -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr (Ptr Widget)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr Widget
val :: Ptr Gtk.Widget.Widget)

-- | Set the value of the “@widget@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #widget
-- @
clearTableChildWidget :: MonadIO m => TableChild -> m ()
clearTableChildWidget :: forall (m :: * -> *). MonadIO m => TableChild -> m ()
clearTableChildWidget TableChild
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr (Ptr Widget) -> Ptr Widget -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr (Ptr Widget)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr Widget
forall a. Ptr a
FP.nullPtr :: Ptr Gtk.Widget.Widget)

#if defined(ENABLE_OVERLOADING)
data TableChildWidgetFieldInfo
instance AttrInfo TableChildWidgetFieldInfo where
    type AttrBaseTypeConstraint TableChildWidgetFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildWidgetFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TableChildWidgetFieldInfo = (~) (Ptr Gtk.Widget.Widget)
    type AttrTransferTypeConstraint TableChildWidgetFieldInfo = (~)(Ptr Gtk.Widget.Widget)
    type AttrTransferType TableChildWidgetFieldInfo = (Ptr Gtk.Widget.Widget)
    type AttrGetType TableChildWidgetFieldInfo = Maybe Gtk.Widget.Widget
    type AttrLabel TableChildWidgetFieldInfo = "widget"
    type AttrOrigin TableChildWidgetFieldInfo = TableChild
    attrGet = getTableChildWidget
    attrSet = setTableChildWidget
    attrConstruct = undefined
    attrClear = clearTableChildWidget
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.widget"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:widget"
        })

tableChild_widget :: AttrLabelProxy "widget"
tableChild_widget = AttrLabelProxy

#endif


-- | Get the value of the “@left_attach@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #leftAttach
-- @
getTableChildLeftAttach :: MonadIO m => TableChild -> m Word16
getTableChildLeftAttach :: forall (m :: * -> *). MonadIO m => TableChild -> m Word16
getTableChildLeftAttach TableChild
s = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word16) -> IO Word16)
-> (Ptr TableChild -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Word16
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@left_attach@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #leftAttach 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildLeftAttach :: MonadIO m => TableChild -> Word16 -> m ()
setTableChildLeftAttach :: forall (m :: * -> *). MonadIO m => TableChild -> Word16 -> m ()
setTableChildLeftAttach TableChild
s Word16
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data TableChildLeftAttachFieldInfo
instance AttrInfo TableChildLeftAttachFieldInfo where
    type AttrBaseTypeConstraint TableChildLeftAttachFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildLeftAttachFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildLeftAttachFieldInfo = (~) Word16
    type AttrTransferTypeConstraint TableChildLeftAttachFieldInfo = (~)Word16
    type AttrTransferType TableChildLeftAttachFieldInfo = Word16
    type AttrGetType TableChildLeftAttachFieldInfo = Word16
    type AttrLabel TableChildLeftAttachFieldInfo = "left_attach"
    type AttrOrigin TableChildLeftAttachFieldInfo = TableChild
    attrGet = getTableChildLeftAttach
    attrSet = setTableChildLeftAttach
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.leftAttach"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:leftAttach"
        })

tableChild_leftAttach :: AttrLabelProxy "leftAttach"
tableChild_leftAttach = AttrLabelProxy

#endif


-- | Get the value of the “@right_attach@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #rightAttach
-- @
getTableChildRightAttach :: MonadIO m => TableChild -> m Word16
getTableChildRightAttach :: forall (m :: * -> *). MonadIO m => TableChild -> m Word16
getTableChildRightAttach TableChild
s = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word16) -> IO Word16)
-> (Ptr TableChild -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
10) :: IO Word16
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@right_attach@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #rightAttach 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildRightAttach :: MonadIO m => TableChild -> Word16 -> m ()
setTableChildRightAttach :: forall (m :: * -> *). MonadIO m => TableChild -> Word16 -> m ()
setTableChildRightAttach TableChild
s Word16
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
10) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data TableChildRightAttachFieldInfo
instance AttrInfo TableChildRightAttachFieldInfo where
    type AttrBaseTypeConstraint TableChildRightAttachFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildRightAttachFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildRightAttachFieldInfo = (~) Word16
    type AttrTransferTypeConstraint TableChildRightAttachFieldInfo = (~)Word16
    type AttrTransferType TableChildRightAttachFieldInfo = Word16
    type AttrGetType TableChildRightAttachFieldInfo = Word16
    type AttrLabel TableChildRightAttachFieldInfo = "right_attach"
    type AttrOrigin TableChildRightAttachFieldInfo = TableChild
    attrGet = getTableChildRightAttach
    attrSet = setTableChildRightAttach
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.rightAttach"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:rightAttach"
        })

tableChild_rightAttach :: AttrLabelProxy "rightAttach"
tableChild_rightAttach = AttrLabelProxy

#endif


-- | Get the value of the “@top_attach@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #topAttach
-- @
getTableChildTopAttach :: MonadIO m => TableChild -> m Word16
getTableChildTopAttach :: forall (m :: * -> *). MonadIO m => TableChild -> m Word16
getTableChildTopAttach TableChild
s = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word16) -> IO Word16)
-> (Ptr TableChild -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) :: IO Word16
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@top_attach@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #topAttach 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildTopAttach :: MonadIO m => TableChild -> Word16 -> m ()
setTableChildTopAttach :: forall (m :: * -> *). MonadIO m => TableChild -> Word16 -> m ()
setTableChildTopAttach TableChild
s Word16
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data TableChildTopAttachFieldInfo
instance AttrInfo TableChildTopAttachFieldInfo where
    type AttrBaseTypeConstraint TableChildTopAttachFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildTopAttachFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildTopAttachFieldInfo = (~) Word16
    type AttrTransferTypeConstraint TableChildTopAttachFieldInfo = (~)Word16
    type AttrTransferType TableChildTopAttachFieldInfo = Word16
    type AttrGetType TableChildTopAttachFieldInfo = Word16
    type AttrLabel TableChildTopAttachFieldInfo = "top_attach"
    type AttrOrigin TableChildTopAttachFieldInfo = TableChild
    attrGet = getTableChildTopAttach
    attrSet = setTableChildTopAttach
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.topAttach"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:topAttach"
        })

tableChild_topAttach :: AttrLabelProxy "topAttach"
tableChild_topAttach = AttrLabelProxy

#endif


-- | Get the value of the “@bottom_attach@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #bottomAttach
-- @
getTableChildBottomAttach :: MonadIO m => TableChild -> m Word16
getTableChildBottomAttach :: forall (m :: * -> *). MonadIO m => TableChild -> m Word16
getTableChildBottomAttach TableChild
s = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word16) -> IO Word16)
-> (Ptr TableChild -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
14) :: IO Word16
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@bottom_attach@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #bottomAttach 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildBottomAttach :: MonadIO m => TableChild -> Word16 -> m ()
setTableChildBottomAttach :: forall (m :: * -> *). MonadIO m => TableChild -> Word16 -> m ()
setTableChildBottomAttach TableChild
s Word16
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
14) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data TableChildBottomAttachFieldInfo
instance AttrInfo TableChildBottomAttachFieldInfo where
    type AttrBaseTypeConstraint TableChildBottomAttachFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildBottomAttachFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildBottomAttachFieldInfo = (~) Word16
    type AttrTransferTypeConstraint TableChildBottomAttachFieldInfo = (~)Word16
    type AttrTransferType TableChildBottomAttachFieldInfo = Word16
    type AttrGetType TableChildBottomAttachFieldInfo = Word16
    type AttrLabel TableChildBottomAttachFieldInfo = "bottom_attach"
    type AttrOrigin TableChildBottomAttachFieldInfo = TableChild
    attrGet = getTableChildBottomAttach
    attrSet = setTableChildBottomAttach
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.bottomAttach"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:bottomAttach"
        })

tableChild_bottomAttach :: AttrLabelProxy "bottomAttach"
tableChild_bottomAttach = AttrLabelProxy

#endif


-- | Get the value of the “@xpadding@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #xpadding
-- @
getTableChildXpadding :: MonadIO m => TableChild -> m Word16
getTableChildXpadding :: forall (m :: * -> *). MonadIO m => TableChild -> m Word16
getTableChildXpadding TableChild
s = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word16) -> IO Word16)
-> (Ptr TableChild -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Word16
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@xpadding@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #xpadding 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildXpadding :: MonadIO m => TableChild -> Word16 -> m ()
setTableChildXpadding :: forall (m :: * -> *). MonadIO m => TableChild -> Word16 -> m ()
setTableChildXpadding TableChild
s Word16
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data TableChildXpaddingFieldInfo
instance AttrInfo TableChildXpaddingFieldInfo where
    type AttrBaseTypeConstraint TableChildXpaddingFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildXpaddingFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildXpaddingFieldInfo = (~) Word16
    type AttrTransferTypeConstraint TableChildXpaddingFieldInfo = (~)Word16
    type AttrTransferType TableChildXpaddingFieldInfo = Word16
    type AttrGetType TableChildXpaddingFieldInfo = Word16
    type AttrLabel TableChildXpaddingFieldInfo = "xpadding"
    type AttrOrigin TableChildXpaddingFieldInfo = TableChild
    attrGet = getTableChildXpadding
    attrSet = setTableChildXpadding
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.xpadding"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:xpadding"
        })

tableChild_xpadding :: AttrLabelProxy "xpadding"
tableChild_xpadding = AttrLabelProxy

#endif


-- | Get the value of the “@ypadding@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #ypadding
-- @
getTableChildYpadding :: MonadIO m => TableChild -> m Word16
getTableChildYpadding :: forall (m :: * -> *). MonadIO m => TableChild -> m Word16
getTableChildYpadding TableChild
s = IO Word16 -> m Word16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word16) -> IO Word16)
-> (Ptr TableChild -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
18) :: IO Word16
    Word16 -> IO Word16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@ypadding@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #ypadding 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildYpadding :: MonadIO m => TableChild -> Word16 -> m ()
setTableChildYpadding :: forall (m :: * -> *). MonadIO m => TableChild -> Word16 -> m ()
setTableChildYpadding TableChild
s Word16
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
18) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data TableChildYpaddingFieldInfo
instance AttrInfo TableChildYpaddingFieldInfo where
    type AttrBaseTypeConstraint TableChildYpaddingFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildYpaddingFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildYpaddingFieldInfo = (~) Word16
    type AttrTransferTypeConstraint TableChildYpaddingFieldInfo = (~)Word16
    type AttrTransferType TableChildYpaddingFieldInfo = Word16
    type AttrGetType TableChildYpaddingFieldInfo = Word16
    type AttrLabel TableChildYpaddingFieldInfo = "ypadding"
    type AttrOrigin TableChildYpaddingFieldInfo = TableChild
    attrGet = getTableChildYpadding
    attrSet = setTableChildYpadding
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.ypadding"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:ypadding"
        })

tableChild_ypadding :: AttrLabelProxy "ypadding"
tableChild_ypadding = AttrLabelProxy

#endif


-- | Get the value of the “@xexpand@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #xexpand
-- @
getTableChildXexpand :: MonadIO m => TableChild -> m Word32
getTableChildXexpand :: forall (m :: * -> *). MonadIO m => TableChild -> m Word32
getTableChildXexpand TableChild
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word32) -> IO Word32)
-> (Ptr TableChild -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@xexpand@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #xexpand 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildXexpand :: MonadIO m => TableChild -> Word32 -> m ()
setTableChildXexpand :: forall (m :: * -> *). MonadIO m => TableChild -> Word32 -> m ()
setTableChildXexpand TableChild
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TableChildXexpandFieldInfo
instance AttrInfo TableChildXexpandFieldInfo where
    type AttrBaseTypeConstraint TableChildXexpandFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildXexpandFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildXexpandFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TableChildXexpandFieldInfo = (~)Word32
    type AttrTransferType TableChildXexpandFieldInfo = Word32
    type AttrGetType TableChildXexpandFieldInfo = Word32
    type AttrLabel TableChildXexpandFieldInfo = "xexpand"
    type AttrOrigin TableChildXexpandFieldInfo = TableChild
    attrGet = getTableChildXexpand
    attrSet = setTableChildXexpand
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.xexpand"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:xexpand"
        })

tableChild_xexpand :: AttrLabelProxy "xexpand"
tableChild_xexpand = AttrLabelProxy

#endif


-- | Get the value of the “@yexpand@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #yexpand
-- @
getTableChildYexpand :: MonadIO m => TableChild -> m Word32
getTableChildYexpand :: forall (m :: * -> *). MonadIO m => TableChild -> m Word32
getTableChildYexpand TableChild
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word32) -> IO Word32)
-> (Ptr TableChild -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@yexpand@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #yexpand 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildYexpand :: MonadIO m => TableChild -> Word32 -> m ()
setTableChildYexpand :: forall (m :: * -> *). MonadIO m => TableChild -> Word32 -> m ()
setTableChildYexpand TableChild
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TableChildYexpandFieldInfo
instance AttrInfo TableChildYexpandFieldInfo where
    type AttrBaseTypeConstraint TableChildYexpandFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildYexpandFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildYexpandFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TableChildYexpandFieldInfo = (~)Word32
    type AttrTransferType TableChildYexpandFieldInfo = Word32
    type AttrGetType TableChildYexpandFieldInfo = Word32
    type AttrLabel TableChildYexpandFieldInfo = "yexpand"
    type AttrOrigin TableChildYexpandFieldInfo = TableChild
    attrGet = getTableChildYexpand
    attrSet = setTableChildYexpand
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.yexpand"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:yexpand"
        })

tableChild_yexpand :: AttrLabelProxy "yexpand"
tableChild_yexpand = AttrLabelProxy

#endif


-- | Get the value of the “@xshrink@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #xshrink
-- @
getTableChildXshrink :: MonadIO m => TableChild -> m Word32
getTableChildXshrink :: forall (m :: * -> *). MonadIO m => TableChild -> m Word32
getTableChildXshrink TableChild
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word32) -> IO Word32)
-> (Ptr TableChild -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@xshrink@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #xshrink 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildXshrink :: MonadIO m => TableChild -> Word32 -> m ()
setTableChildXshrink :: forall (m :: * -> *). MonadIO m => TableChild -> Word32 -> m ()
setTableChildXshrink TableChild
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TableChildXshrinkFieldInfo
instance AttrInfo TableChildXshrinkFieldInfo where
    type AttrBaseTypeConstraint TableChildXshrinkFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildXshrinkFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildXshrinkFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TableChildXshrinkFieldInfo = (~)Word32
    type AttrTransferType TableChildXshrinkFieldInfo = Word32
    type AttrGetType TableChildXshrinkFieldInfo = Word32
    type AttrLabel TableChildXshrinkFieldInfo = "xshrink"
    type AttrOrigin TableChildXshrinkFieldInfo = TableChild
    attrGet = getTableChildXshrink
    attrSet = setTableChildXshrink
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.xshrink"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:xshrink"
        })

tableChild_xshrink :: AttrLabelProxy "xshrink"
tableChild_xshrink = AttrLabelProxy

#endif


-- | Get the value of the “@yshrink@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #yshrink
-- @
getTableChildYshrink :: MonadIO m => TableChild -> m Word32
getTableChildYshrink :: forall (m :: * -> *). MonadIO m => TableChild -> m Word32
getTableChildYshrink TableChild
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word32) -> IO Word32)
-> (Ptr TableChild -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@yshrink@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #yshrink 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildYshrink :: MonadIO m => TableChild -> Word32 -> m ()
setTableChildYshrink :: forall (m :: * -> *). MonadIO m => TableChild -> Word32 -> m ()
setTableChildYshrink TableChild
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TableChildYshrinkFieldInfo
instance AttrInfo TableChildYshrinkFieldInfo where
    type AttrBaseTypeConstraint TableChildYshrinkFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildYshrinkFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildYshrinkFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TableChildYshrinkFieldInfo = (~)Word32
    type AttrTransferType TableChildYshrinkFieldInfo = Word32
    type AttrGetType TableChildYshrinkFieldInfo = Word32
    type AttrLabel TableChildYshrinkFieldInfo = "yshrink"
    type AttrOrigin TableChildYshrinkFieldInfo = TableChild
    attrGet = getTableChildYshrink
    attrSet = setTableChildYshrink
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.yshrink"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:yshrink"
        })

tableChild_yshrink :: AttrLabelProxy "yshrink"
tableChild_yshrink = AttrLabelProxy

#endif


-- | Get the value of the “@xfill@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #xfill
-- @
getTableChildXfill :: MonadIO m => TableChild -> m Word32
getTableChildXfill :: forall (m :: * -> *). MonadIO m => TableChild -> m Word32
getTableChildXfill TableChild
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word32) -> IO Word32)
-> (Ptr TableChild -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@xfill@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #xfill 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildXfill :: MonadIO m => TableChild -> Word32 -> m ()
setTableChildXfill :: forall (m :: * -> *). MonadIO m => TableChild -> Word32 -> m ()
setTableChildXfill TableChild
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TableChildXfillFieldInfo
instance AttrInfo TableChildXfillFieldInfo where
    type AttrBaseTypeConstraint TableChildXfillFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildXfillFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildXfillFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TableChildXfillFieldInfo = (~)Word32
    type AttrTransferType TableChildXfillFieldInfo = Word32
    type AttrGetType TableChildXfillFieldInfo = Word32
    type AttrLabel TableChildXfillFieldInfo = "xfill"
    type AttrOrigin TableChildXfillFieldInfo = TableChild
    attrGet = getTableChildXfill
    attrSet = setTableChildXfill
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.xfill"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:xfill"
        })

tableChild_xfill :: AttrLabelProxy "xfill"
tableChild_xfill = AttrLabelProxy

#endif


-- | Get the value of the “@yfill@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' tableChild #yfill
-- @
getTableChildYfill :: MonadIO m => TableChild -> m Word32
getTableChildYfill :: forall (m :: * -> *). MonadIO m => TableChild -> m Word32
getTableChildYfill TableChild
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO Word32) -> IO Word32)
-> (Ptr TableChild -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@yfill@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' tableChild [ #yfill 'Data.GI.Base.Attributes.:=' value ]
-- @
setTableChildYfill :: MonadIO m => TableChild -> Word32 -> m ()
setTableChildYfill :: forall (m :: * -> *). MonadIO m => TableChild -> Word32 -> m ()
setTableChildYfill TableChild
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TableChild -> (Ptr TableChild -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TableChild
s ((Ptr TableChild -> IO ()) -> IO ())
-> (Ptr TableChild -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TableChild
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TableChild
ptr Ptr TableChild -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TableChildYfillFieldInfo
instance AttrInfo TableChildYfillFieldInfo where
    type AttrBaseTypeConstraint TableChildYfillFieldInfo = (~) TableChild
    type AttrAllowedOps TableChildYfillFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TableChildYfillFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TableChildYfillFieldInfo = (~)Word32
    type AttrTransferType TableChildYfillFieldInfo = Word32
    type AttrGetType TableChildYfillFieldInfo = Word32
    type AttrLabel TableChildYfillFieldInfo = "yfill"
    type AttrOrigin TableChildYfillFieldInfo = TableChild
    attrGet = getTableChildYfill
    attrSet = setTableChildYfill
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.TableChild.yfill"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Structs-TableChild.html#g:attr:yfill"
        })

tableChild_yfill :: AttrLabelProxy "yfill"
tableChild_yfill = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TableChild
type instance O.AttributeList TableChild = TableChildAttributeList
type TableChildAttributeList = ('[ '("widget", TableChildWidgetFieldInfo), '("leftAttach", TableChildLeftAttachFieldInfo), '("rightAttach", TableChildRightAttachFieldInfo), '("topAttach", TableChildTopAttachFieldInfo), '("bottomAttach", TableChildBottomAttachFieldInfo), '("xpadding", TableChildXpaddingFieldInfo), '("ypadding", TableChildYpaddingFieldInfo), '("xexpand", TableChildXexpandFieldInfo), '("yexpand", TableChildYexpandFieldInfo), '("xshrink", TableChildXshrinkFieldInfo), '("yshrink", TableChildYshrinkFieldInfo), '("xfill", TableChildXfillFieldInfo), '("yfill", TableChildYfillFieldInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTableChildMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveTableChildMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTableChildMethod t TableChild, O.OverloadedMethod info TableChild p) => OL.IsLabel t (TableChild -> 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 ~ ResolveTableChildMethod t TableChild, O.OverloadedMethod info TableChild p, R.HasField t TableChild p) => R.HasField t TableChild p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveTableChildMethod t TableChild, O.OverloadedMethodInfo info TableChild) => OL.IsLabel t (O.MethodProxy info TableChild) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif