{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Layout properties for children of t'GI.Gtk.Objects.GridLayout.GridLayout'.

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

module GI.Gtk.Objects.GridLayoutChild
    ( 

-- * Exported types
    GridLayoutChild(..)                     ,
    IsGridLayoutChild                       ,
    toGridLayoutChild                       ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveGridLayoutChildMethod            ,
#endif


-- ** getColumnSpan #method:getColumnSpan#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildGetColumnSpanMethodInfo  ,
#endif
    gridLayoutChildGetColumnSpan            ,


-- ** getLeftAttach #method:getLeftAttach#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildGetLeftAttachMethodInfo  ,
#endif
    gridLayoutChildGetLeftAttach            ,


-- ** getRowSpan #method:getRowSpan#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildGetRowSpanMethodInfo     ,
#endif
    gridLayoutChildGetRowSpan               ,


-- ** getTopAttach #method:getTopAttach#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildGetTopAttachMethodInfo   ,
#endif
    gridLayoutChildGetTopAttach             ,


-- ** setColumnSpan #method:setColumnSpan#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildSetColumnSpanMethodInfo  ,
#endif
    gridLayoutChildSetColumnSpan            ,


-- ** setLeftAttach #method:setLeftAttach#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildSetLeftAttachMethodInfo  ,
#endif
    gridLayoutChildSetLeftAttach            ,


-- ** setRowSpan #method:setRowSpan#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildSetRowSpanMethodInfo     ,
#endif
    gridLayoutChildSetRowSpan               ,


-- ** setTopAttach #method:setTopAttach#

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildSetTopAttachMethodInfo   ,
#endif
    gridLayoutChildSetTopAttach             ,




 -- * Properties
-- ** columnSpan #attr:columnSpan#
-- | The number of columns the child spans to.

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildColumnSpanPropertyInfo   ,
#endif
    constructGridLayoutChildColumnSpan      ,
    getGridLayoutChildColumnSpan            ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutChildColumnSpan               ,
#endif
    setGridLayoutChildColumnSpan            ,


-- ** leftAttach #attr:leftAttach#
-- | The column number to attach the left side of the child to.

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildLeftAttachPropertyInfo   ,
#endif
    constructGridLayoutChildLeftAttach      ,
    getGridLayoutChildLeftAttach            ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutChildLeftAttach               ,
#endif
    setGridLayoutChildLeftAttach            ,


-- ** rowSpan #attr:rowSpan#
-- | The number of rows the child spans to.

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildRowSpanPropertyInfo      ,
#endif
    constructGridLayoutChildRowSpan         ,
    getGridLayoutChildRowSpan               ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutChildRowSpan                  ,
#endif
    setGridLayoutChildRowSpan               ,


-- ** topAttach #attr:topAttach#
-- | The row number to attach the top side of the child to.

#if defined(ENABLE_OVERLOADING)
    GridLayoutChildTopAttachPropertyInfo    ,
#endif
    constructGridLayoutChildTopAttach       ,
    getGridLayoutChildTopAttach             ,
#if defined(ENABLE_OVERLOADING)
    gridLayoutChildTopAttach                ,
#endif
    setGridLayoutChildTopAttach             ,




    ) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutChild as Gtk.LayoutChild

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

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

foreign import ccall "gtk_grid_layout_child_get_type"
    c_gtk_grid_layout_child_get_type :: IO B.Types.GType

instance B.Types.TypedObject GridLayoutChild where
    glibType :: IO GType
glibType = IO GType
c_gtk_grid_layout_child_get_type

instance B.Types.GObject GridLayoutChild

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

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

instance O.HasParentTypes GridLayoutChild
type instance O.ParentTypes GridLayoutChild = '[Gtk.LayoutChild.LayoutChild, GObject.Object.Object]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveGridLayoutChildMethod (t :: Symbol) (o :: *) :: * where
    ResolveGridLayoutChildMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGridLayoutChildMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGridLayoutChildMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGridLayoutChildMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGridLayoutChildMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGridLayoutChildMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGridLayoutChildMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGridLayoutChildMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGridLayoutChildMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGridLayoutChildMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGridLayoutChildMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGridLayoutChildMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGridLayoutChildMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGridLayoutChildMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGridLayoutChildMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGridLayoutChildMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGridLayoutChildMethod "getChildWidget" o = Gtk.LayoutChild.LayoutChildGetChildWidgetMethodInfo
    ResolveGridLayoutChildMethod "getColumnSpan" o = GridLayoutChildGetColumnSpanMethodInfo
    ResolveGridLayoutChildMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGridLayoutChildMethod "getLayoutManager" o = Gtk.LayoutChild.LayoutChildGetLayoutManagerMethodInfo
    ResolveGridLayoutChildMethod "getLeftAttach" o = GridLayoutChildGetLeftAttachMethodInfo
    ResolveGridLayoutChildMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGridLayoutChildMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGridLayoutChildMethod "getRowSpan" o = GridLayoutChildGetRowSpanMethodInfo
    ResolveGridLayoutChildMethod "getTopAttach" o = GridLayoutChildGetTopAttachMethodInfo
    ResolveGridLayoutChildMethod "setColumnSpan" o = GridLayoutChildSetColumnSpanMethodInfo
    ResolveGridLayoutChildMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGridLayoutChildMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGridLayoutChildMethod "setLeftAttach" o = GridLayoutChildSetLeftAttachMethodInfo
    ResolveGridLayoutChildMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGridLayoutChildMethod "setRowSpan" o = GridLayoutChildSetRowSpanMethodInfo
    ResolveGridLayoutChildMethod "setTopAttach" o = GridLayoutChildSetTopAttachMethodInfo
    ResolveGridLayoutChildMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "column-span"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@column-span@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gridLayoutChild #columnSpan
-- @
getGridLayoutChildColumnSpan :: (MonadIO m, IsGridLayoutChild o) => o -> m Int32
getGridLayoutChildColumnSpan :: o -> m Int32
getGridLayoutChildColumnSpan o
obj = IO Int32 -> m Int32
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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"column-span"

-- | Set the value of the “@column-span@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayoutChild [ #columnSpan 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutChildColumnSpan :: (MonadIO m, IsGridLayoutChild o) => o -> Int32 -> m ()
setGridLayoutChildColumnSpan :: o -> Int32 -> m ()
setGridLayoutChildColumnSpan o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"column-span" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@column-span@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutChildColumnSpan :: (IsGridLayoutChild o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridLayoutChildColumnSpan :: Int32 -> m (GValueConstruct o)
constructGridLayoutChildColumnSpan Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"column-span" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildColumnSpanPropertyInfo
instance AttrInfo GridLayoutChildColumnSpanPropertyInfo where
    type AttrAllowedOps GridLayoutChildColumnSpanPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutChildColumnSpanPropertyInfo = IsGridLayoutChild
    type AttrSetTypeConstraint GridLayoutChildColumnSpanPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutChildColumnSpanPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutChildColumnSpanPropertyInfo = Int32
    type AttrGetType GridLayoutChildColumnSpanPropertyInfo = Int32
    type AttrLabel GridLayoutChildColumnSpanPropertyInfo = "column-span"
    type AttrOrigin GridLayoutChildColumnSpanPropertyInfo = GridLayoutChild
    attrGet = getGridLayoutChildColumnSpan
    attrSet = setGridLayoutChildColumnSpan
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutChildColumnSpan
    attrClear = undefined
#endif

-- VVV Prop "left-attach"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@left-attach@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gridLayoutChild #leftAttach
-- @
getGridLayoutChildLeftAttach :: (MonadIO m, IsGridLayoutChild o) => o -> m Int32
getGridLayoutChildLeftAttach :: o -> m Int32
getGridLayoutChildLeftAttach o
obj = IO Int32 -> m Int32
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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"left-attach"

-- | Set the value of the “@left-attach@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayoutChild [ #leftAttach 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutChildLeftAttach :: (MonadIO m, IsGridLayoutChild o) => o -> Int32 -> m ()
setGridLayoutChildLeftAttach :: o -> Int32 -> m ()
setGridLayoutChildLeftAttach o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"left-attach" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@left-attach@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutChildLeftAttach :: (IsGridLayoutChild o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridLayoutChildLeftAttach :: Int32 -> m (GValueConstruct o)
constructGridLayoutChildLeftAttach Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"left-attach" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildLeftAttachPropertyInfo
instance AttrInfo GridLayoutChildLeftAttachPropertyInfo where
    type AttrAllowedOps GridLayoutChildLeftAttachPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutChildLeftAttachPropertyInfo = IsGridLayoutChild
    type AttrSetTypeConstraint GridLayoutChildLeftAttachPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutChildLeftAttachPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutChildLeftAttachPropertyInfo = Int32
    type AttrGetType GridLayoutChildLeftAttachPropertyInfo = Int32
    type AttrLabel GridLayoutChildLeftAttachPropertyInfo = "left-attach"
    type AttrOrigin GridLayoutChildLeftAttachPropertyInfo = GridLayoutChild
    attrGet = getGridLayoutChildLeftAttach
    attrSet = setGridLayoutChildLeftAttach
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutChildLeftAttach
    attrClear = undefined
#endif

-- VVV Prop "row-span"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@row-span@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gridLayoutChild #rowSpan
-- @
getGridLayoutChildRowSpan :: (MonadIO m, IsGridLayoutChild o) => o -> m Int32
getGridLayoutChildRowSpan :: o -> m Int32
getGridLayoutChildRowSpan o
obj = IO Int32 -> m Int32
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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"row-span"

-- | Set the value of the “@row-span@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayoutChild [ #rowSpan 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutChildRowSpan :: (MonadIO m, IsGridLayoutChild o) => o -> Int32 -> m ()
setGridLayoutChildRowSpan :: o -> Int32 -> m ()
setGridLayoutChildRowSpan o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"row-span" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@row-span@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutChildRowSpan :: (IsGridLayoutChild o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridLayoutChildRowSpan :: Int32 -> m (GValueConstruct o)
constructGridLayoutChildRowSpan Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"row-span" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildRowSpanPropertyInfo
instance AttrInfo GridLayoutChildRowSpanPropertyInfo where
    type AttrAllowedOps GridLayoutChildRowSpanPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutChildRowSpanPropertyInfo = IsGridLayoutChild
    type AttrSetTypeConstraint GridLayoutChildRowSpanPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutChildRowSpanPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutChildRowSpanPropertyInfo = Int32
    type AttrGetType GridLayoutChildRowSpanPropertyInfo = Int32
    type AttrLabel GridLayoutChildRowSpanPropertyInfo = "row-span"
    type AttrOrigin GridLayoutChildRowSpanPropertyInfo = GridLayoutChild
    attrGet = getGridLayoutChildRowSpan
    attrSet = setGridLayoutChildRowSpan
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutChildRowSpan
    attrClear = undefined
#endif

-- VVV Prop "top-attach"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@top-attach@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gridLayoutChild #topAttach
-- @
getGridLayoutChildTopAttach :: (MonadIO m, IsGridLayoutChild o) => o -> m Int32
getGridLayoutChildTopAttach :: o -> m Int32
getGridLayoutChildTopAttach o
obj = IO Int32 -> m Int32
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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"top-attach"

-- | Set the value of the “@top-attach@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gridLayoutChild [ #topAttach 'Data.GI.Base.Attributes.:=' value ]
-- @
setGridLayoutChildTopAttach :: (MonadIO m, IsGridLayoutChild o) => o -> Int32 -> m ()
setGridLayoutChildTopAttach :: o -> Int32 -> m ()
setGridLayoutChildTopAttach o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"top-attach" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@top-attach@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGridLayoutChildTopAttach :: (IsGridLayoutChild o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructGridLayoutChildTopAttach :: Int32 -> m (GValueConstruct o)
constructGridLayoutChildTopAttach Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"top-attach" Int32
val

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildTopAttachPropertyInfo
instance AttrInfo GridLayoutChildTopAttachPropertyInfo where
    type AttrAllowedOps GridLayoutChildTopAttachPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GridLayoutChildTopAttachPropertyInfo = IsGridLayoutChild
    type AttrSetTypeConstraint GridLayoutChildTopAttachPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint GridLayoutChildTopAttachPropertyInfo = (~) Int32
    type AttrTransferType GridLayoutChildTopAttachPropertyInfo = Int32
    type AttrGetType GridLayoutChildTopAttachPropertyInfo = Int32
    type AttrLabel GridLayoutChildTopAttachPropertyInfo = "top-attach"
    type AttrOrigin GridLayoutChildTopAttachPropertyInfo = GridLayoutChild
    attrGet = getGridLayoutChildTopAttach
    attrSet = setGridLayoutChildTopAttach
    attrTransfer _ v = do
        return v
    attrConstruct = constructGridLayoutChildTopAttach
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GridLayoutChild
type instance O.AttributeList GridLayoutChild = GridLayoutChildAttributeList
type GridLayoutChildAttributeList = ('[ '("childWidget", Gtk.LayoutChild.LayoutChildChildWidgetPropertyInfo), '("columnSpan", GridLayoutChildColumnSpanPropertyInfo), '("layoutManager", Gtk.LayoutChild.LayoutChildLayoutManagerPropertyInfo), '("leftAttach", GridLayoutChildLeftAttachPropertyInfo), '("rowSpan", GridLayoutChildRowSpanPropertyInfo), '("topAttach", GridLayoutChildTopAttachPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
gridLayoutChildColumnSpan :: AttrLabelProxy "columnSpan"
gridLayoutChildColumnSpan = AttrLabelProxy

gridLayoutChildLeftAttach :: AttrLabelProxy "leftAttach"
gridLayoutChildLeftAttach = AttrLabelProxy

gridLayoutChildRowSpan :: AttrLabelProxy "rowSpan"
gridLayoutChildRowSpan = AttrLabelProxy

gridLayoutChildTopAttach :: AttrLabelProxy "topAttach"
gridLayoutChildTopAttach = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "gtk_grid_layout_child_get_column_span" gtk_grid_layout_child_get_column_span :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    IO Int32

-- | Retrieves the number of columns that /@child@/ spans to.
gridLayoutChildGetColumnSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild'
    -> m Int32
    -- ^ __Returns:__ the number of columns
gridLayoutChildGetColumnSpan :: a -> m Int32
gridLayoutChildGetColumnSpan a
child = IO Int32 -> m Int32
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 GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Int32
result <- Ptr GridLayoutChild -> IO Int32
gtk_grid_layout_child_get_column_span Ptr GridLayoutChild
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildGetColumnSpanMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayoutChild a) => O.MethodInfo GridLayoutChildGetColumnSpanMethodInfo a signature where
    overloadedMethod = gridLayoutChildGetColumnSpan

#endif

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

foreign import ccall "gtk_grid_layout_child_get_left_attach" gtk_grid_layout_child_get_left_attach :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    IO Int32

-- | Retrieves the column number to which /@child@/ attaches its left side.
gridLayoutChildGetLeftAttach ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild'
    -> m Int32
    -- ^ __Returns:__ the column number
gridLayoutChildGetLeftAttach :: a -> m Int32
gridLayoutChildGetLeftAttach a
child = IO Int32 -> m Int32
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 GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Int32
result <- Ptr GridLayoutChild -> IO Int32
gtk_grid_layout_child_get_left_attach Ptr GridLayoutChild
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildGetLeftAttachMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayoutChild a) => O.MethodInfo GridLayoutChildGetLeftAttachMethodInfo a signature where
    overloadedMethod = gridLayoutChildGetLeftAttach

#endif

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

foreign import ccall "gtk_grid_layout_child_get_row_span" gtk_grid_layout_child_get_row_span :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    IO Int32

-- | Retrieves the number of rows that /@child@/ spans to.
gridLayoutChildGetRowSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild'
    -> m Int32
    -- ^ __Returns:__ the number of row
gridLayoutChildGetRowSpan :: a -> m Int32
gridLayoutChildGetRowSpan a
child = IO Int32 -> m Int32
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 GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Int32
result <- Ptr GridLayoutChild -> IO Int32
gtk_grid_layout_child_get_row_span Ptr GridLayoutChild
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildGetRowSpanMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayoutChild a) => O.MethodInfo GridLayoutChildGetRowSpanMethodInfo a signature where
    overloadedMethod = gridLayoutChildGetRowSpan

#endif

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

foreign import ccall "gtk_grid_layout_child_get_top_attach" gtk_grid_layout_child_get_top_attach :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    IO Int32

-- | Retrieves the row number to which /@child@/ attaches its top side.
gridLayoutChildGetTopAttach ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild'
    -> m Int32
    -- ^ __Returns:__ the row number
gridLayoutChildGetTopAttach :: a -> m Int32
gridLayoutChildGetTopAttach a
child = IO Int32 -> m Int32
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 GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Int32
result <- Ptr GridLayoutChild -> IO Int32
gtk_grid_layout_child_get_top_attach Ptr GridLayoutChild
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildGetTopAttachMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsGridLayoutChild a) => O.MethodInfo GridLayoutChildGetTopAttachMethodInfo a signature where
    overloadedMethod = gridLayoutChildGetTopAttach

#endif

-- method GridLayoutChild::set_column_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayoutChild" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayoutChild"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "span"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the span of @child" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_child_set_column_span" gtk_grid_layout_child_set_column_span :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    Int32 ->                                -- span : TBasicType TInt
    IO ()

-- | Sets the number of columns /@child@/ spans to.
gridLayoutChildSetColumnSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild'
    -> Int32
    -- ^ /@span@/: the span of /@child@/
    -> m ()
gridLayoutChildSetColumnSpan :: a -> Int32 -> m ()
gridLayoutChildSetColumnSpan a
child Int32
span = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Ptr GridLayoutChild -> Int32 -> IO ()
gtk_grid_layout_child_set_column_span Ptr GridLayoutChild
child' Int32
span
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildSetColumnSpanMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayoutChild a) => O.MethodInfo GridLayoutChildSetColumnSpanMethodInfo a signature where
    overloadedMethod = gridLayoutChildSetColumnSpan

#endif

-- method GridLayoutChild::set_left_attach
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayoutChild" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayoutChild"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attach"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attach point for @child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_child_set_left_attach" gtk_grid_layout_child_set_left_attach :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    Int32 ->                                -- attach : TBasicType TInt
    IO ()

-- | Sets the column number to attach the left side of /@child@/.
gridLayoutChildSetLeftAttach ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild'
    -> Int32
    -- ^ /@attach@/: the attach point for /@child@/
    -> m ()
gridLayoutChildSetLeftAttach :: a -> Int32 -> m ()
gridLayoutChildSetLeftAttach a
child Int32
attach = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Ptr GridLayoutChild -> Int32 -> IO ()
gtk_grid_layout_child_set_left_attach Ptr GridLayoutChild
child' Int32
attach
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildSetLeftAttachMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayoutChild a) => O.MethodInfo GridLayoutChildSetLeftAttachMethodInfo a signature where
    overloadedMethod = gridLayoutChildSetLeftAttach

#endif

-- method GridLayoutChild::set_row_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayoutChild" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayoutChild"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "span"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the span of @child" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_child_set_row_span" gtk_grid_layout_child_set_row_span :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    Int32 ->                                -- span : TBasicType TInt
    IO ()

-- | Sets the number of rows /@child@/ spans to.
gridLayoutChildSetRowSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild'
    -> Int32
    -- ^ /@span@/: the span of /@child@/
    -> m ()
gridLayoutChildSetRowSpan :: a -> Int32 -> m ()
gridLayoutChildSetRowSpan a
child Int32
span = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Ptr GridLayoutChild -> Int32 -> IO ()
gtk_grid_layout_child_set_row_span Ptr GridLayoutChild
child' Int32
span
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildSetRowSpanMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayoutChild a) => O.MethodInfo GridLayoutChildSetRowSpanMethodInfo a signature where
    overloadedMethod = gridLayoutChildSetRowSpan

#endif

-- method GridLayoutChild::set_top_attach
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "child"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "GridLayoutChild" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkGridLayoutChild"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attach"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attach point for @child"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_grid_layout_child_set_top_attach" gtk_grid_layout_child_set_top_attach :: 
    Ptr GridLayoutChild ->                  -- child : TInterface (Name {namespace = "Gtk", name = "GridLayoutChild"})
    Int32 ->                                -- attach : TBasicType TInt
    IO ()

-- | Sets the row number to attach the top side of /@child@/.
gridLayoutChildSetTopAttach ::
    (B.CallStack.HasCallStack, MonadIO m, IsGridLayoutChild a) =>
    a
    -- ^ /@child@/: a t'GI.Gtk.Objects.GridLayoutChild.GridLayoutChild'
    -> Int32
    -- ^ /@attach@/: the attach point for /@child@/
    -> m ()
gridLayoutChildSetTopAttach :: a -> Int32 -> m ()
gridLayoutChildSetTopAttach a
child Int32
attach = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GridLayoutChild
child' <- a -> IO (Ptr GridLayoutChild)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
child
    Ptr GridLayoutChild -> Int32 -> IO ()
gtk_grid_layout_child_set_top_attach Ptr GridLayoutChild
child' Int32
attach
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
child
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GridLayoutChildSetTopAttachMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGridLayoutChild a) => O.MethodInfo GridLayoutChildSetTopAttachMethodInfo a signature where
    overloadedMethod = gridLayoutChildSetTopAttach

#endif