{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.Grid
    ( 
    Grid(..)                                ,
    IsGrid                                  ,
    toGrid                                  ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveGridMethod                       ,
#endif
#if defined(ENABLE_OVERLOADING)
    GridAttachMethodInfo                    ,
#endif
    gridAttach                              ,
#if defined(ENABLE_OVERLOADING)
    GridAttachNextToMethodInfo              ,
#endif
    gridAttachNextTo                        ,
#if defined(ENABLE_OVERLOADING)
    GridGetBaselineRowMethodInfo            ,
#endif
    gridGetBaselineRow                      ,
#if defined(ENABLE_OVERLOADING)
    GridGetChildAtMethodInfo                ,
#endif
    gridGetChildAt                          ,
#if defined(ENABLE_OVERLOADING)
    GridGetColumnHomogeneousMethodInfo      ,
#endif
    gridGetColumnHomogeneous                ,
#if defined(ENABLE_OVERLOADING)
    GridGetColumnSpacingMethodInfo          ,
#endif
    gridGetColumnSpacing                    ,
#if defined(ENABLE_OVERLOADING)
    GridGetRowBaselinePositionMethodInfo    ,
#endif
    gridGetRowBaselinePosition              ,
#if defined(ENABLE_OVERLOADING)
    GridGetRowHomogeneousMethodInfo         ,
#endif
    gridGetRowHomogeneous                   ,
#if defined(ENABLE_OVERLOADING)
    GridGetRowSpacingMethodInfo             ,
#endif
    gridGetRowSpacing                       ,
#if defined(ENABLE_OVERLOADING)
    GridInsertColumnMethodInfo              ,
#endif
    gridInsertColumn                        ,
#if defined(ENABLE_OVERLOADING)
    GridInsertNextToMethodInfo              ,
#endif
    gridInsertNextTo                        ,
#if defined(ENABLE_OVERLOADING)
    GridInsertRowMethodInfo                 ,
#endif
    gridInsertRow                           ,
    gridNew                                 ,
#if defined(ENABLE_OVERLOADING)
    GridRemoveColumnMethodInfo              ,
#endif
    gridRemoveColumn                        ,
#if defined(ENABLE_OVERLOADING)
    GridRemoveRowMethodInfo                 ,
#endif
    gridRemoveRow                           ,
#if defined(ENABLE_OVERLOADING)
    GridSetBaselineRowMethodInfo            ,
#endif
    gridSetBaselineRow                      ,
#if defined(ENABLE_OVERLOADING)
    GridSetColumnHomogeneousMethodInfo      ,
#endif
    gridSetColumnHomogeneous                ,
#if defined(ENABLE_OVERLOADING)
    GridSetColumnSpacingMethodInfo          ,
#endif
    gridSetColumnSpacing                    ,
#if defined(ENABLE_OVERLOADING)
    GridSetRowBaselinePositionMethodInfo    ,
#endif
    gridSetRowBaselinePosition              ,
#if defined(ENABLE_OVERLOADING)
    GridSetRowHomogeneousMethodInfo         ,
#endif
    gridSetRowHomogeneous                   ,
#if defined(ENABLE_OVERLOADING)
    GridSetRowSpacingMethodInfo             ,
#endif
    gridSetRowSpacing                       ,
 
#if defined(ENABLE_OVERLOADING)
    GridBaselineRowPropertyInfo             ,
#endif
    constructGridBaselineRow                ,
    getGridBaselineRow                      ,
#if defined(ENABLE_OVERLOADING)
    gridBaselineRow                         ,
#endif
    setGridBaselineRow                      ,
#if defined(ENABLE_OVERLOADING)
    GridColumnHomogeneousPropertyInfo       ,
#endif
    constructGridColumnHomogeneous          ,
    getGridColumnHomogeneous                ,
#if defined(ENABLE_OVERLOADING)
    gridColumnHomogeneous                   ,
#endif
    setGridColumnHomogeneous                ,
#if defined(ENABLE_OVERLOADING)
    GridColumnSpacingPropertyInfo           ,
#endif
    constructGridColumnSpacing              ,
    getGridColumnSpacing                    ,
#if defined(ENABLE_OVERLOADING)
    gridColumnSpacing                       ,
#endif
    setGridColumnSpacing                    ,
#if defined(ENABLE_OVERLOADING)
    GridRowHomogeneousPropertyInfo          ,
#endif
    constructGridRowHomogeneous             ,
    getGridRowHomogeneous                   ,
#if defined(ENABLE_OVERLOADING)
    gridRowHomogeneous                      ,
#endif
    setGridRowHomogeneous                   ,
#if defined(ENABLE_OVERLOADING)
    GridRowSpacingPropertyInfo              ,
#endif
    constructGridRowSpacing                 ,
    getGridRowSpacing                       ,
#if defined(ENABLE_OVERLOADING)
    gridRowSpacing                          ,
#endif
    setGridRowSpacing                       ,
    ) 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
#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.Orientable as Gtk.Orientable
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 qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
#endif
newtype Grid = Grid (SP.ManagedPtr Grid)
    deriving (Grid -> Grid -> Bool
(Grid -> Grid -> Bool) -> (Grid -> Grid -> Bool) -> Eq Grid
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Grid -> Grid -> Bool
== :: Grid -> Grid -> Bool
$c/= :: Grid -> Grid -> Bool
/= :: Grid -> Grid -> Bool
Eq)
instance SP.ManagedPtrNewtype Grid where
    toManagedPtr :: Grid -> ManagedPtr Grid
toManagedPtr (Grid ManagedPtr Grid
p) = ManagedPtr Grid
p
foreign import ccall "gtk_grid_get_type"
    c_gtk_grid_get_type :: IO B.Types.GType
instance B.Types.TypedObject Grid where
    glibType :: IO GType
glibType = IO GType
c_gtk_grid_get_type
instance B.Types.GObject Grid
class (SP.GObject o, O.IsDescendantOf Grid o) => IsGrid o
instance (SP.GObject o, O.IsDescendantOf Grid o) => IsGrid o
instance O.HasParentTypes Grid
type instance O.ParentTypes Grid = '[Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.Orientable.Orientable]
toGrid :: (MIO.MonadIO m, IsGrid o) => o -> m Grid
toGrid :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> m Grid
toGrid = IO Grid -> m Grid
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Grid -> m Grid) -> (o -> IO Grid) -> o -> m Grid
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Grid -> Grid) -> o -> IO Grid
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Grid -> Grid
Grid
instance B.GValue.IsGValue (Maybe Grid) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_grid_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Grid -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Grid
P.Nothing = Ptr GValue -> Ptr Grid -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Grid
forall a. Ptr a
FP.nullPtr :: FP.Ptr Grid)
    gvalueSet_ Ptr GValue
gv (P.Just Grid
obj) = Grid -> (Ptr Grid -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Grid
obj (Ptr GValue -> Ptr Grid -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Grid)
gvalueGet_ Ptr GValue
gv = do
        Ptr Grid
ptr <- Ptr GValue -> IO (Ptr Grid)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Grid)
        if Ptr Grid
ptr Ptr Grid -> Ptr Grid -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Grid
forall a. Ptr a
FP.nullPtr
        then Grid -> Maybe Grid
forall a. a -> Maybe a
P.Just (Grid -> Maybe Grid) -> IO Grid -> IO (Maybe Grid)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Grid -> Grid) -> Ptr Grid -> IO Grid
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Grid -> Grid
Grid Ptr Grid
ptr
        else Maybe Grid -> IO (Maybe Grid)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Grid
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveGridMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveGridMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveGridMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolveGridMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveGridMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveGridMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
    ResolveGridMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
    ResolveGridMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveGridMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveGridMethod "attach" o = GridAttachMethodInfo
    ResolveGridMethod "attachNextTo" o = GridAttachNextToMethodInfo
    ResolveGridMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGridMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGridMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveGridMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
    ResolveGridMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveGridMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
    ResolveGridMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
    ResolveGridMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
    ResolveGridMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
    ResolveGridMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    ResolveGridMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
    ResolveGridMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveGridMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveGridMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveGridMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveGridMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveGridMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveGridMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveGridMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveGridMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveGridMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveGridMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveGridMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
    ResolveGridMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveGridMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveGridMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveGridMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveGridMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveGridMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveGridMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveGridMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveGridMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
    ResolveGridMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveGridMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveGridMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveGridMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveGridMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveGridMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveGridMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveGridMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveGridMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveGridMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveGridMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveGridMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveGridMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
    ResolveGridMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
    ResolveGridMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveGridMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveGridMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveGridMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
    ResolveGridMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
    ResolveGridMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveGridMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveGridMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolveGridMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGridMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolveGridMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
    ResolveGridMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGridMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGridMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveGridMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
    ResolveGridMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveGridMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveGridMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveGridMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveGridMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveGridMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
    ResolveGridMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
    ResolveGridMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveGridMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveGridMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
    ResolveGridMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveGridMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveGridMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveGridMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveGridMethod "insertColumn" o = GridInsertColumnMethodInfo
    ResolveGridMethod "insertNextTo" o = GridInsertNextToMethodInfo
    ResolveGridMethod "insertRow" o = GridInsertRowMethodInfo
    ResolveGridMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
    ResolveGridMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveGridMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
    ResolveGridMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveGridMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGridMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveGridMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveGridMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveGridMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveGridMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveGridMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveGridMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveGridMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveGridMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveGridMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveGridMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
    ResolveGridMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
    ResolveGridMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
    ResolveGridMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
    ResolveGridMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
    ResolveGridMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
    ResolveGridMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
    ResolveGridMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGridMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGridMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
    ResolveGridMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
    ResolveGridMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
    ResolveGridMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
    ResolveGridMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
    ResolveGridMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveGridMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
    ResolveGridMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
    ResolveGridMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveGridMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveGridMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveGridMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
    ResolveGridMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
    ResolveGridMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveGridMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveGridMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveGridMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGridMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGridMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
    ResolveGridMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
    ResolveGridMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolveGridMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveGridMethod "removeColumn" o = GridRemoveColumnMethodInfo
    ResolveGridMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveGridMethod "removeRow" o = GridRemoveRowMethodInfo
    ResolveGridMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveGridMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
    ResolveGridMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
    ResolveGridMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
    ResolveGridMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
    ResolveGridMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveGridMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
    ResolveGridMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGridMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
    ResolveGridMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
    ResolveGridMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
    ResolveGridMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveGridMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
    ResolveGridMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
    ResolveGridMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveGridMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
    ResolveGridMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
    ResolveGridMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGridMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGridMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
    ResolveGridMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
    ResolveGridMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
    ResolveGridMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGridMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveGridMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveGridMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveGridMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveGridMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveGridMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGridMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
    ResolveGridMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
    ResolveGridMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveGridMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGridMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveGridMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveGridMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveGridMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveGridMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
    ResolveGridMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveGridMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveGridMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveGridMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
    ResolveGridMethod "getBaselineRow" o = GridGetBaselineRowMethodInfo
    ResolveGridMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
    ResolveGridMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
    ResolveGridMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveGridMethod "getChildAt" o = GridGetChildAtMethodInfo
    ResolveGridMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
    ResolveGridMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveGridMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolveGridMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
    ResolveGridMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveGridMethod "getColumnHomogeneous" o = GridGetColumnHomogeneousMethodInfo
    ResolveGridMethod "getColumnSpacing" o = GridGetColumnSpacingMethodInfo
    ResolveGridMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
    ResolveGridMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGridMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
    ResolveGridMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
    ResolveGridMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveGridMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveGridMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
    ResolveGridMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
    ResolveGridMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
    ResolveGridMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
    ResolveGridMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolveGridMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveGridMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    ResolveGridMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveGridMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveGridMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveGridMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveGridMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveGridMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
    ResolveGridMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveGridMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveGridMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveGridMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveGridMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveGridMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveGridMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
    ResolveGridMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
    ResolveGridMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveGridMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveGridMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveGridMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
    ResolveGridMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveGridMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
    ResolveGridMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveGridMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveGridMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveGridMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveGridMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
    ResolveGridMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveGridMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    ResolveGridMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
    ResolveGridMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
    ResolveGridMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
    ResolveGridMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
    ResolveGridMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveGridMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
    ResolveGridMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
    ResolveGridMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGridMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGridMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveGridMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveGridMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveGridMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
    ResolveGridMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
    ResolveGridMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
    ResolveGridMethod "getRowBaselinePosition" o = GridGetRowBaselinePositionMethodInfo
    ResolveGridMethod "getRowHomogeneous" o = GridGetRowHomogeneousMethodInfo
    ResolveGridMethod "getRowSpacing" o = GridGetRowSpacingMethodInfo
    ResolveGridMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveGridMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
    ResolveGridMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveGridMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveGridMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveGridMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
    ResolveGridMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveGridMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
    ResolveGridMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveGridMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveGridMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveGridMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveGridMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveGridMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveGridMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveGridMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveGridMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
    ResolveGridMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveGridMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveGridMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveGridMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
    ResolveGridMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
    ResolveGridMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveGridMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
    ResolveGridMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
    ResolveGridMethod "setBaselineRow" o = GridSetBaselineRowMethodInfo
    ResolveGridMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
    ResolveGridMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveGridMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
    ResolveGridMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveGridMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveGridMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
    ResolveGridMethod "setColumnHomogeneous" o = GridSetColumnHomogeneousMethodInfo
    ResolveGridMethod "setColumnSpacing" o = GridSetColumnSpacingMethodInfo
    ResolveGridMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
    ResolveGridMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGridMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGridMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
    ResolveGridMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
    ResolveGridMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveGridMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
    ResolveGridMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
    ResolveGridMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
    ResolveGridMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
    ResolveGridMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolveGridMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveGridMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolveGridMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveGridMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveGridMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveGridMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveGridMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
    ResolveGridMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveGridMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveGridMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
    ResolveGridMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveGridMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveGridMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
    ResolveGridMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
    ResolveGridMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveGridMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveGridMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveGridMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
    ResolveGridMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveGridMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveGridMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveGridMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
    ResolveGridMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGridMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
    ResolveGridMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
    ResolveGridMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveGridMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
    ResolveGridMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
    ResolveGridMethod "setRowBaselinePosition" o = GridSetRowBaselinePositionMethodInfo
    ResolveGridMethod "setRowHomogeneous" o = GridSetRowHomogeneousMethodInfo
    ResolveGridMethod "setRowSpacing" o = GridSetRowSpacingMethodInfo
    ResolveGridMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveGridMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveGridMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
    ResolveGridMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveGridMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
    ResolveGridMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveGridMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveGridMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveGridMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveGridMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveGridMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveGridMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveGridMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveGridMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
    ResolveGridMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
    ResolveGridMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveGridMethod t Grid, O.OverloadedMethod info Grid p) => OL.IsLabel t (Grid -> 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 ~ ResolveGridMethod t Grid, O.OverloadedMethod info Grid p, R.HasField t Grid p) => R.HasField t Grid p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveGridMethod t Grid, O.OverloadedMethodInfo info Grid) => OL.IsLabel t (O.MethodProxy info Grid) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
   
   
   
getGridBaselineRow :: (MonadIO m, IsGrid o) => o -> m Int32
getGridBaselineRow :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> m Int32
getGridBaselineRow o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"baseline-row"
setGridBaselineRow :: (MonadIO m, IsGrid o) => o -> Int32 -> m ()
setGridBaselineRow :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> Int32 -> m ()
setGridBaselineRow o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"baseline-row" Int32
val
constructGridBaselineRow :: (IsGrid o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridBaselineRow :: forall o (m :: * -> *).
(IsGrid o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructGridBaselineRow Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"baseline-row" Int32
val
#if defined(ENABLE_OVERLOADING)
data GridBaselineRowPropertyInfo
instance AttrInfo GridBaselineRowPropertyInfo where
    type AttrAllowedOps GridBaselineRowPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridBaselineRowPropertyInfo = IsGrid
    type AttrSetTypeConstraint GridBaselineRowPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridBaselineRowPropertyInfo = (~) Int32
    type AttrTransferType GridBaselineRowPropertyInfo = Int32
    type AttrGetType GridBaselineRowPropertyInfo = Int32
    type AttrLabel GridBaselineRowPropertyInfo = "baseline-row"
    type AttrOrigin GridBaselineRowPropertyInfo = Grid
    attrGet = getGridBaselineRow
    attrSet = setGridBaselineRow
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridBaselineRow
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.baselineRow"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#g:attr:baselineRow"
        })
#endif
   
   
   
getGridColumnHomogeneous :: (MonadIO m, IsGrid o) => o -> m Bool
getGridColumnHomogeneous :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> m Bool
getGridColumnHomogeneous o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"column-homogeneous"
setGridColumnHomogeneous :: (MonadIO m, IsGrid o) => o -> Bool -> m ()
setGridColumnHomogeneous :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> Bool -> m ()
setGridColumnHomogeneous o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"column-homogeneous" Bool
val
constructGridColumnHomogeneous :: (IsGrid o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructGridColumnHomogeneous :: forall o (m :: * -> *).
(IsGrid o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructGridColumnHomogeneous Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"column-homogeneous" Bool
val
#if defined(ENABLE_OVERLOADING)
data GridColumnHomogeneousPropertyInfo
instance AttrInfo GridColumnHomogeneousPropertyInfo where
    type AttrAllowedOps GridColumnHomogeneousPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridColumnHomogeneousPropertyInfo = IsGrid
    type AttrSetTypeConstraint GridColumnHomogeneousPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint GridColumnHomogeneousPropertyInfo = (~) Bool
    type AttrTransferType GridColumnHomogeneousPropertyInfo = Bool
    type AttrGetType GridColumnHomogeneousPropertyInfo = Bool
    type AttrLabel GridColumnHomogeneousPropertyInfo = "column-homogeneous"
    type AttrOrigin GridColumnHomogeneousPropertyInfo = Grid
    attrGet = getGridColumnHomogeneous
    attrSet = setGridColumnHomogeneous
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridColumnHomogeneous
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.columnHomogeneous"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#g:attr:columnHomogeneous"
        })
#endif
   
   
   
getGridColumnSpacing :: (MonadIO m, IsGrid o) => o -> m Int32
getGridColumnSpacing :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> m Int32
getGridColumnSpacing o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"column-spacing"
setGridColumnSpacing :: (MonadIO m, IsGrid o) => o -> Int32 -> m ()
setGridColumnSpacing :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> Int32 -> m ()
setGridColumnSpacing o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"column-spacing" Int32
val
constructGridColumnSpacing :: (IsGrid o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridColumnSpacing :: forall o (m :: * -> *).
(IsGrid o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructGridColumnSpacing Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"column-spacing" Int32
val
#if defined(ENABLE_OVERLOADING)
data GridColumnSpacingPropertyInfo
instance AttrInfo GridColumnSpacingPropertyInfo where
    type AttrAllowedOps GridColumnSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridColumnSpacingPropertyInfo = IsGrid
    type AttrSetTypeConstraint GridColumnSpacingPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridColumnSpacingPropertyInfo = (~) Int32
    type AttrTransferType GridColumnSpacingPropertyInfo = Int32
    type AttrGetType GridColumnSpacingPropertyInfo = Int32
    type AttrLabel GridColumnSpacingPropertyInfo = "column-spacing"
    type AttrOrigin GridColumnSpacingPropertyInfo = Grid
    attrGet = getGridColumnSpacing
    attrSet = setGridColumnSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridColumnSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.columnSpacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#g:attr:columnSpacing"
        })
#endif
   
   
   
getGridRowHomogeneous :: (MonadIO m, IsGrid o) => o -> m Bool
getGridRowHomogeneous :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> m Bool
getGridRowHomogeneous o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"row-homogeneous"
setGridRowHomogeneous :: (MonadIO m, IsGrid o) => o -> Bool -> m ()
setGridRowHomogeneous :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> Bool -> m ()
setGridRowHomogeneous o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"row-homogeneous" Bool
val
constructGridRowHomogeneous :: (IsGrid o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructGridRowHomogeneous :: forall o (m :: * -> *).
(IsGrid o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructGridRowHomogeneous Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"row-homogeneous" Bool
val
#if defined(ENABLE_OVERLOADING)
data GridRowHomogeneousPropertyInfo
instance AttrInfo GridRowHomogeneousPropertyInfo where
    type AttrAllowedOps GridRowHomogeneousPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridRowHomogeneousPropertyInfo = IsGrid
    type AttrSetTypeConstraint GridRowHomogeneousPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint GridRowHomogeneousPropertyInfo = (~) Bool
    type AttrTransferType GridRowHomogeneousPropertyInfo = Bool
    type AttrGetType GridRowHomogeneousPropertyInfo = Bool
    type AttrLabel GridRowHomogeneousPropertyInfo = "row-homogeneous"
    type AttrOrigin GridRowHomogeneousPropertyInfo = Grid
    attrGet = getGridRowHomogeneous
    attrSet = setGridRowHomogeneous
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridRowHomogeneous
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.rowHomogeneous"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#g:attr:rowHomogeneous"
        })
#endif
   
   
   
getGridRowSpacing :: (MonadIO m, IsGrid o) => o -> m Int32
getGridRowSpacing :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> m Int32
getGridRowSpacing o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"row-spacing"
setGridRowSpacing :: (MonadIO m, IsGrid o) => o -> Int32 -> m ()
setGridRowSpacing :: forall (m :: * -> *) o. (MonadIO m, IsGrid o) => o -> Int32 -> m ()
setGridRowSpacing o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"row-spacing" Int32
val
constructGridRowSpacing :: (IsGrid o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridRowSpacing :: forall o (m :: * -> *).
(IsGrid o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructGridRowSpacing Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"row-spacing" Int32
val
#if defined(ENABLE_OVERLOADING)
data GridRowSpacingPropertyInfo
instance AttrInfo GridRowSpacingPropertyInfo where
    type AttrAllowedOps GridRowSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridRowSpacingPropertyInfo = IsGrid
    type AttrSetTypeConstraint GridRowSpacingPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridRowSpacingPropertyInfo = (~) Int32
    type AttrTransferType GridRowSpacingPropertyInfo = Int32
    type AttrGetType GridRowSpacingPropertyInfo = Int32
    type AttrLabel GridRowSpacingPropertyInfo = "row-spacing"
    type AttrOrigin GridRowSpacingPropertyInfo = Grid
    attrGet = getGridRowSpacing
    attrSet = setGridRowSpacing
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridRowSpacing
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.rowSpacing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#g:attr:rowSpacing"
        })
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Grid
type instance O.AttributeList Grid = GridAttributeList
type GridAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("baselineRow", GridBaselineRowPropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("columnHomogeneous", GridColumnHomogeneousPropertyInfo), '("columnSpacing", GridColumnSpacingPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("rowHomogeneous", GridRowHomogeneousPropertyInfo), '("rowSpacing", GridRowSpacingPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
gridBaselineRow :: AttrLabelProxy "baselineRow"
gridBaselineRow = AttrLabelProxy
gridColumnHomogeneous :: AttrLabelProxy "columnHomogeneous"
gridColumnHomogeneous = AttrLabelProxy
gridColumnSpacing :: AttrLabelProxy "columnSpacing"
gridColumnSpacing = AttrLabelProxy
gridRowHomogeneous :: AttrLabelProxy "rowHomogeneous"
gridRowHomogeneous = AttrLabelProxy
gridRowSpacing :: AttrLabelProxy "rowSpacing"
gridRowSpacing = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Grid = GridSignalList
type GridSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("setFocusChild", Gtk.Container.ContainerSetFocusChildSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_grid_new" gtk_grid_new :: 
    IO (Ptr Grid)
gridNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Grid
    
gridNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Grid
gridNew  = IO Grid -> m Grid
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Grid -> m Grid) -> IO Grid -> m Grid
forall a b. (a -> b) -> a -> b
$ do
    Ptr Grid
result <- IO (Ptr Grid)
gtk_grid_new
    Text -> Ptr Grid -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"gridNew" Ptr Grid
result
    Grid
result' <- ((ManagedPtr Grid -> Grid) -> Ptr Grid -> IO Grid
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Grid -> Grid
Grid) Ptr Grid
result
    Grid -> IO Grid
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Grid
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_grid_attach" gtk_grid_attach :: 
    Ptr Grid ->                             
    Ptr Gtk.Widget.Widget ->                
    Int32 ->                                
    Int32 ->                                
    Int32 ->                                
    Int32 ->                                
    IO ()
gridAttach ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a, Gtk.Widget.IsWidget b) =>
    a
    
    -> b
    
    -> Int32
    
    -> Int32
    
    -> Int32
    
    -> Int32
    
    -> m ()
gridAttach :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsGrid a, IsWidget b) =>
a -> b -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
gridAttach a
grid b
child Int32
left Int32
top Int32
width Int32
height = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr Grid -> Ptr Widget -> Int32 -> Int32 -> Int32 -> Int32 -> IO ()
gtk_grid_attach Ptr Grid
grid' Ptr Widget
child' Int32
left Int32
top Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridAttachMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsGrid a, Gtk.Widget.IsWidget b) => O.OverloadedMethod GridAttachMethodInfo a signature where
    overloadedMethod = gridAttach
instance O.OverloadedMethodInfo GridAttachMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridAttach",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridAttach"
        })
#endif
foreign import ccall "gtk_grid_attach_next_to" gtk_grid_attach_next_to :: 
    Ptr Grid ->                             
    Ptr Gtk.Widget.Widget ->                
    Ptr Gtk.Widget.Widget ->                
    CUInt ->                                
    Int32 ->                                
    Int32 ->                                
    IO ()
gridAttachNextTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a, Gtk.Widget.IsWidget b, Gtk.Widget.IsWidget c) =>
    a
    
    -> b
    
    -> Maybe (c)
    
    
    -> Gtk.Enums.PositionType
    
    -> Int32
    
    -> Int32
    
    -> m ()
gridAttachNextTo :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsGrid a, IsWidget b, IsWidget c) =>
a -> b -> Maybe c -> PositionType -> Int32 -> Int32 -> m ()
gridAttachNextTo a
grid b
child Maybe c
sibling PositionType
side Int32
width Int32
height = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr Widget
maybeSibling <- case Maybe c
sibling of
        Maybe c
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
FP.nullPtr
        Just c
jSibling -> do
            Ptr Widget
jSibling' <- c -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jSibling
            Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jSibling'
    let side' :: CUInt
side' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PositionType -> Int) -> PositionType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionType -> Int
forall a. Enum a => a -> Int
fromEnum) PositionType
side
    Ptr Grid
-> Ptr Widget -> Ptr Widget -> CUInt -> Int32 -> Int32 -> IO ()
gtk_grid_attach_next_to Ptr Grid
grid' Ptr Widget
child' Ptr Widget
maybeSibling CUInt
side' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
sibling c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridAttachNextToMethodInfo
instance (signature ~ (b -> Maybe (c) -> Gtk.Enums.PositionType -> Int32 -> Int32 -> m ()), MonadIO m, IsGrid a, Gtk.Widget.IsWidget b, Gtk.Widget.IsWidget c) => O.OverloadedMethod GridAttachNextToMethodInfo a signature where
    overloadedMethod = gridAttachNextTo
instance O.OverloadedMethodInfo GridAttachNextToMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridAttachNextTo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridAttachNextTo"
        })
#endif
foreign import ccall "gtk_grid_get_baseline_row" gtk_grid_get_baseline_row :: 
    Ptr Grid ->                             
    IO Int32
gridGetBaselineRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> m Int32
    
gridGetBaselineRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> m Int32
gridGetBaselineRow a
grid = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Int32
result <- Ptr Grid -> IO Int32
gtk_grid_get_baseline_row Ptr Grid
grid'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data GridGetBaselineRowMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGrid a) => O.OverloadedMethod GridGetBaselineRowMethodInfo a signature where
    overloadedMethod = gridGetBaselineRow
instance O.OverloadedMethodInfo GridGetBaselineRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridGetBaselineRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridGetBaselineRow"
        })
#endif
foreign import ccall "gtk_grid_get_child_at" gtk_grid_get_child_at :: 
    Ptr Grid ->                             
    Int32 ->                                
    Int32 ->                                
    IO (Ptr Gtk.Widget.Widget)
gridGetChildAt ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Int32
    
    -> Int32
    
    -> m (Maybe Gtk.Widget.Widget)
    
gridGetChildAt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Int32 -> Int32 -> m (Maybe Widget)
gridGetChildAt a
grid Int32
left Int32
top = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Widget
result <- Ptr Grid -> Int32 -> Int32 -> IO (Ptr Widget)
gtk_grid_get_child_at Ptr Grid
grid' Int32
left Int32
top
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Maybe Widget -> IO (Maybe Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult
#if defined(ENABLE_OVERLOADING)
data GridGetChildAtMethodInfo
instance (signature ~ (Int32 -> Int32 -> m (Maybe Gtk.Widget.Widget)), MonadIO m, IsGrid a) => O.OverloadedMethod GridGetChildAtMethodInfo a signature where
    overloadedMethod = gridGetChildAt
instance O.OverloadedMethodInfo GridGetChildAtMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridGetChildAt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridGetChildAt"
        })
#endif
foreign import ccall "gtk_grid_get_column_homogeneous" gtk_grid_get_column_homogeneous :: 
    Ptr Grid ->                             
    IO CInt
gridGetColumnHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> m Bool
    
gridGetColumnHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> m Bool
gridGetColumnHomogeneous a
grid = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    CInt
result <- Ptr Grid -> IO CInt
gtk_grid_get_column_homogeneous Ptr Grid
grid'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data GridGetColumnHomogeneousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGrid a) => O.OverloadedMethod GridGetColumnHomogeneousMethodInfo a signature where
    overloadedMethod = gridGetColumnHomogeneous
instance O.OverloadedMethodInfo GridGetColumnHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridGetColumnHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridGetColumnHomogeneous"
        })
#endif
foreign import ccall "gtk_grid_get_column_spacing" gtk_grid_get_column_spacing :: 
    Ptr Grid ->                             
    IO Word32
gridGetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> m Word32
    
gridGetColumnSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> m Word32
gridGetColumnSpacing a
grid = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Word32
result <- Ptr Grid -> IO Word32
gtk_grid_get_column_spacing Ptr Grid
grid'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data GridGetColumnSpacingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsGrid a) => O.OverloadedMethod GridGetColumnSpacingMethodInfo a signature where
    overloadedMethod = gridGetColumnSpacing
instance O.OverloadedMethodInfo GridGetColumnSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridGetColumnSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridGetColumnSpacing"
        })
#endif
foreign import ccall "gtk_grid_get_row_baseline_position" gtk_grid_get_row_baseline_position :: 
    Ptr Grid ->                             
    Int32 ->                                
    IO CUInt
gridGetRowBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Int32
    
    -> m Gtk.Enums.BaselinePosition
    
gridGetRowBaselinePosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Int32 -> m BaselinePosition
gridGetRowBaselinePosition a
grid Int32
row = IO BaselinePosition -> m BaselinePosition
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BaselinePosition -> m BaselinePosition)
-> IO BaselinePosition -> m BaselinePosition
forall a b. (a -> b) -> a -> b
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    CUInt
result <- Ptr Grid -> Int32 -> IO CUInt
gtk_grid_get_row_baseline_position Ptr Grid
grid' Int32
row
    let result' :: BaselinePosition
result' = (Int -> BaselinePosition
forall a. Enum a => Int -> a
toEnum (Int -> BaselinePosition)
-> (CUInt -> Int) -> CUInt -> BaselinePosition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    BaselinePosition -> IO BaselinePosition
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BaselinePosition
result'
#if defined(ENABLE_OVERLOADING)
data GridGetRowBaselinePositionMethodInfo
instance (signature ~ (Int32 -> m Gtk.Enums.BaselinePosition), MonadIO m, IsGrid a) => O.OverloadedMethod GridGetRowBaselinePositionMethodInfo a signature where
    overloadedMethod = gridGetRowBaselinePosition
instance O.OverloadedMethodInfo GridGetRowBaselinePositionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridGetRowBaselinePosition",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridGetRowBaselinePosition"
        })
#endif
foreign import ccall "gtk_grid_get_row_homogeneous" gtk_grid_get_row_homogeneous :: 
    Ptr Grid ->                             
    IO CInt
gridGetRowHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> m Bool
    
gridGetRowHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> m Bool
gridGetRowHomogeneous a
grid = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    CInt
result <- Ptr Grid -> IO CInt
gtk_grid_get_row_homogeneous Ptr Grid
grid'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data GridGetRowHomogeneousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGrid a) => O.OverloadedMethod GridGetRowHomogeneousMethodInfo a signature where
    overloadedMethod = gridGetRowHomogeneous
instance O.OverloadedMethodInfo GridGetRowHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridGetRowHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridGetRowHomogeneous"
        })
#endif
foreign import ccall "gtk_grid_get_row_spacing" gtk_grid_get_row_spacing :: 
    Ptr Grid ->                             
    IO Word32
gridGetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> m Word32
    
gridGetRowSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> m Word32
gridGetRowSpacing a
grid = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Word32
result <- Ptr Grid -> IO Word32
gtk_grid_get_row_spacing Ptr Grid
grid'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data GridGetRowSpacingMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsGrid a) => O.OverloadedMethod GridGetRowSpacingMethodInfo a signature where
    overloadedMethod = gridGetRowSpacing
instance O.OverloadedMethodInfo GridGetRowSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridGetRowSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridGetRowSpacing"
        })
#endif
foreign import ccall "gtk_grid_insert_column" gtk_grid_insert_column :: 
    Ptr Grid ->                             
    Int32 ->                                
    IO ()
gridInsertColumn ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Int32
    
    -> m ()
gridInsertColumn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Int32 -> m ()
gridInsertColumn a
grid Int32
position = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Grid -> Int32 -> IO ()
gtk_grid_insert_column Ptr Grid
grid' Int32
position
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridInsertColumnMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridInsertColumnMethodInfo a signature where
    overloadedMethod = gridInsertColumn
instance O.OverloadedMethodInfo GridInsertColumnMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridInsertColumn",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridInsertColumn"
        })
#endif
foreign import ccall "gtk_grid_insert_next_to" gtk_grid_insert_next_to :: 
    Ptr Grid ->                             
    Ptr Gtk.Widget.Widget ->                
    CUInt ->                                
    IO ()
gridInsertNextTo ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a, Gtk.Widget.IsWidget b) =>
    a
    
    -> b
    
    
    -> Gtk.Enums.PositionType
    
    -> m ()
gridInsertNextTo :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsGrid a, IsWidget b) =>
a -> b -> PositionType -> m ()
gridInsertNextTo a
grid b
sibling PositionType
side = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Widget
sibling' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
sibling
    let side' :: CUInt
side' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PositionType -> Int) -> PositionType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PositionType -> Int
forall a. Enum a => a -> Int
fromEnum) PositionType
side
    Ptr Grid -> Ptr Widget -> CUInt -> IO ()
gtk_grid_insert_next_to Ptr Grid
grid' Ptr Widget
sibling' CUInt
side'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
sibling
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridInsertNextToMethodInfo
instance (signature ~ (b -> Gtk.Enums.PositionType -> m ()), MonadIO m, IsGrid a, Gtk.Widget.IsWidget b) => O.OverloadedMethod GridInsertNextToMethodInfo a signature where
    overloadedMethod = gridInsertNextTo
instance O.OverloadedMethodInfo GridInsertNextToMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridInsertNextTo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridInsertNextTo"
        })
#endif
foreign import ccall "gtk_grid_insert_row" gtk_grid_insert_row :: 
    Ptr Grid ->                             
    Int32 ->                                
    IO ()
gridInsertRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Int32
    
    -> m ()
gridInsertRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Int32 -> m ()
gridInsertRow a
grid Int32
position = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Grid -> Int32 -> IO ()
gtk_grid_insert_row Ptr Grid
grid' Int32
position
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridInsertRowMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridInsertRowMethodInfo a signature where
    overloadedMethod = gridInsertRow
instance O.OverloadedMethodInfo GridInsertRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridInsertRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridInsertRow"
        })
#endif
foreign import ccall "gtk_grid_remove_column" gtk_grid_remove_column :: 
    Ptr Grid ->                             
    Int32 ->                                
    IO ()
gridRemoveColumn ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Int32
    
    -> m ()
gridRemoveColumn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Int32 -> m ()
gridRemoveColumn a
grid Int32
position = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Grid -> Int32 -> IO ()
gtk_grid_remove_column Ptr Grid
grid' Int32
position
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridRemoveColumnMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridRemoveColumnMethodInfo a signature where
    overloadedMethod = gridRemoveColumn
instance O.OverloadedMethodInfo GridRemoveColumnMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridRemoveColumn",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridRemoveColumn"
        })
#endif
foreign import ccall "gtk_grid_remove_row" gtk_grid_remove_row :: 
    Ptr Grid ->                             
    Int32 ->                                
    IO ()
gridRemoveRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Int32
    
    -> m ()
gridRemoveRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Int32 -> m ()
gridRemoveRow a
grid Int32
position = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Grid -> Int32 -> IO ()
gtk_grid_remove_row Ptr Grid
grid' Int32
position
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridRemoveRowMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridRemoveRowMethodInfo a signature where
    overloadedMethod = gridRemoveRow
instance O.OverloadedMethodInfo GridRemoveRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridRemoveRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridRemoveRow"
        })
#endif
foreign import ccall "gtk_grid_set_baseline_row" gtk_grid_set_baseline_row :: 
    Ptr Grid ->                             
    Int32 ->                                
    IO ()
gridSetBaselineRow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Int32
    
    -> m ()
gridSetBaselineRow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Int32 -> m ()
gridSetBaselineRow a
grid Int32
row = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Grid -> Int32 -> IO ()
gtk_grid_set_baseline_row Ptr Grid
grid' Int32
row
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridSetBaselineRowMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridSetBaselineRowMethodInfo a signature where
    overloadedMethod = gridSetBaselineRow
instance O.OverloadedMethodInfo GridSetBaselineRowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridSetBaselineRow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridSetBaselineRow"
        })
#endif
foreign import ccall "gtk_grid_set_column_homogeneous" gtk_grid_set_column_homogeneous :: 
    Ptr Grid ->                             
    CInt ->                                 
    IO ()
gridSetColumnHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Bool
    
    -> m ()
gridSetColumnHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Bool -> m ()
gridSetColumnHomogeneous a
grid Bool
homogeneous = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    let homogeneous' :: CInt
homogeneous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
homogeneous
    Ptr Grid -> CInt -> IO ()
gtk_grid_set_column_homogeneous Ptr Grid
grid' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridSetColumnHomogeneousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridSetColumnHomogeneousMethodInfo a signature where
    overloadedMethod = gridSetColumnHomogeneous
instance O.OverloadedMethodInfo GridSetColumnHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridSetColumnHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridSetColumnHomogeneous"
        })
#endif
foreign import ccall "gtk_grid_set_column_spacing" gtk_grid_set_column_spacing :: 
    Ptr Grid ->                             
    Word32 ->                               
    IO ()
gridSetColumnSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Word32
    
    -> m ()
gridSetColumnSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Word32 -> m ()
gridSetColumnSpacing a
grid Word32
spacing = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Grid -> Word32 -> IO ()
gtk_grid_set_column_spacing Ptr Grid
grid' Word32
spacing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridSetColumnSpacingMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridSetColumnSpacingMethodInfo a signature where
    overloadedMethod = gridSetColumnSpacing
instance O.OverloadedMethodInfo GridSetColumnSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridSetColumnSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridSetColumnSpacing"
        })
#endif
foreign import ccall "gtk_grid_set_row_baseline_position" gtk_grid_set_row_baseline_position :: 
    Ptr Grid ->                             
    Int32 ->                                
    CUInt ->                                
    IO ()
gridSetRowBaselinePosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Int32
    
    -> Gtk.Enums.BaselinePosition
    
    -> m ()
gridSetRowBaselinePosition :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Int32 -> BaselinePosition -> m ()
gridSetRowBaselinePosition a
grid Int32
row BaselinePosition
pos = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    let pos' :: CUInt
pos' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (BaselinePosition -> Int) -> BaselinePosition -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BaselinePosition -> Int
forall a. Enum a => a -> Int
fromEnum) BaselinePosition
pos
    Ptr Grid -> Int32 -> CUInt -> IO ()
gtk_grid_set_row_baseline_position Ptr Grid
grid' Int32
row CUInt
pos'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridSetRowBaselinePositionMethodInfo
instance (signature ~ (Int32 -> Gtk.Enums.BaselinePosition -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridSetRowBaselinePositionMethodInfo a signature where
    overloadedMethod = gridSetRowBaselinePosition
instance O.OverloadedMethodInfo GridSetRowBaselinePositionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridSetRowBaselinePosition",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridSetRowBaselinePosition"
        })
#endif
foreign import ccall "gtk_grid_set_row_homogeneous" gtk_grid_set_row_homogeneous :: 
    Ptr Grid ->                             
    CInt ->                                 
    IO ()
gridSetRowHomogeneous ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Bool
    
    -> m ()
gridSetRowHomogeneous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Bool -> m ()
gridSetRowHomogeneous a
grid Bool
homogeneous = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    let homogeneous' :: CInt
homogeneous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
homogeneous
    Ptr Grid -> CInt -> IO ()
gtk_grid_set_row_homogeneous Ptr Grid
grid' CInt
homogeneous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridSetRowHomogeneousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridSetRowHomogeneousMethodInfo a signature where
    overloadedMethod = gridSetRowHomogeneous
instance O.OverloadedMethodInfo GridSetRowHomogeneousMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridSetRowHomogeneous",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridSetRowHomogeneous"
        })
#endif
foreign import ccall "gtk_grid_set_row_spacing" gtk_grid_set_row_spacing :: 
    Ptr Grid ->                             
    Word32 ->                               
    IO ()
gridSetRowSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsGrid a) =>
    a
    
    -> Word32
    
    -> m ()
gridSetRowSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGrid a) =>
a -> Word32 -> m ()
gridSetRowSpacing a
grid Word32
spacing = 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
$ do
    Ptr Grid
grid' <- a -> IO (Ptr Grid)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
grid
    Ptr Grid -> Word32 -> IO ()
gtk_grid_set_row_spacing Ptr Grid
grid' Word32
spacing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
grid
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GridSetRowSpacingMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsGrid a) => O.OverloadedMethod GridSetRowSpacingMethodInfo a signature where
    overloadedMethod = gridSetRowSpacing
instance O.OverloadedMethodInfo GridSetRowSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Grid.gridSetRowSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.43/docs/GI-Gtk-Objects-Grid.html#v:gridSetRowSpacing"
        })
#endif