{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Being t'GI.Atk.Interfaces.Table.Table' a component which present elements ordered via rows
-- and columns, an t'GI.Atk.Interfaces.TableCell.TableCell' is the interface which each of those
-- elements, so \"cells\" should implement.
-- 
-- See also t'GI.Atk.Interfaces.Table.Table'.

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

module GI.Atk.Interfaces.TableCell
    ( 

-- * Exported types
    TableCell(..)                           ,
    noTableCell                             ,
    IsTableCell                             ,
    toTableCell                             ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveTableCellMethod                  ,
#endif


-- ** getColumnHeaderCells #method:getColumnHeaderCells#

#if defined(ENABLE_OVERLOADING)
    TableCellGetColumnHeaderCellsMethodInfo ,
#endif
    tableCellGetColumnHeaderCells           ,


-- ** getColumnSpan #method:getColumnSpan#

#if defined(ENABLE_OVERLOADING)
    TableCellGetColumnSpanMethodInfo        ,
#endif
    tableCellGetColumnSpan                  ,


-- ** getPosition #method:getPosition#

#if defined(ENABLE_OVERLOADING)
    TableCellGetPositionMethodInfo          ,
#endif
    tableCellGetPosition                    ,


-- ** getRowColumnSpan #method:getRowColumnSpan#

#if defined(ENABLE_OVERLOADING)
    TableCellGetRowColumnSpanMethodInfo     ,
#endif
    tableCellGetRowColumnSpan               ,


-- ** getRowHeaderCells #method:getRowHeaderCells#

#if defined(ENABLE_OVERLOADING)
    TableCellGetRowHeaderCellsMethodInfo    ,
#endif
    tableCellGetRowHeaderCells              ,


-- ** getRowSpan #method:getRowSpan#

#if defined(ENABLE_OVERLOADING)
    TableCellGetRowSpanMethodInfo           ,
#endif
    tableCellGetRowSpan                     ,


-- ** getTable #method:getTable#

#if defined(ENABLE_OVERLOADING)
    TableCellGetTableMethodInfo             ,
#endif
    tableCellGetTable                       ,




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

-- interface TableCell 
-- | Memory-managed wrapper type.
newtype TableCell = TableCell (ManagedPtr TableCell)
    deriving (TableCell -> TableCell -> Bool
(TableCell -> TableCell -> Bool)
-> (TableCell -> TableCell -> Bool) -> Eq TableCell
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableCell -> TableCell -> Bool
$c/= :: TableCell -> TableCell -> Bool
== :: TableCell -> TableCell -> Bool
$c== :: TableCell -> TableCell -> Bool
Eq)
-- | A convenience alias for `Nothing` :: `Maybe` `TableCell`.
noTableCell :: Maybe TableCell
noTableCell :: Maybe TableCell
noTableCell = Maybe TableCell
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TableCell = TableCellSignalList
type TableCellSignalList = ('[ '("activeDescendantChanged", Atk.Object.ObjectActiveDescendantChangedSignalInfo), '("childrenChanged", Atk.Object.ObjectChildrenChangedSignalInfo), '("focusEvent", Atk.Object.ObjectFocusEventSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("propertyChange", Atk.Object.ObjectPropertyChangeSignalInfo), '("stateChange", Atk.Object.ObjectStateChangeSignalInfo), '("visibleDataChanged", Atk.Object.ObjectVisibleDataChangedSignalInfo)] :: [(Symbol, *)])

#endif

foreign import ccall "atk_table_cell_get_type"
    c_atk_table_cell_get_type :: IO GType

instance GObject TableCell where
    gobjectType :: IO GType
gobjectType = IO GType
c_atk_table_cell_get_type
    

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

-- | Type class for types which can be safely cast to `TableCell`, for instance with `toTableCell`.
class (GObject o, O.IsDescendantOf TableCell o) => IsTableCell o
instance (GObject o, O.IsDescendantOf TableCell o) => IsTableCell o

instance O.HasParentTypes TableCell
type instance O.ParentTypes TableCell = '[Atk.Object.Object, GObject.Object.Object]

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TableCell
type instance O.AttributeList TableCell = TableCellAttributeList
type TableCellAttributeList = ('[ '("accessibleComponentLayer", Atk.Object.ObjectAccessibleComponentLayerPropertyInfo), '("accessibleComponentMdiZorder", Atk.Object.ObjectAccessibleComponentMdiZorderPropertyInfo), '("accessibleDescription", Atk.Object.ObjectAccessibleDescriptionPropertyInfo), '("accessibleHypertextNlinks", Atk.Object.ObjectAccessibleHypertextNlinksPropertyInfo), '("accessibleName", Atk.Object.ObjectAccessibleNamePropertyInfo), '("accessibleParent", Atk.Object.ObjectAccessibleParentPropertyInfo), '("accessibleRole", Atk.Object.ObjectAccessibleRolePropertyInfo), '("accessibleTableCaption", Atk.Object.ObjectAccessibleTableCaptionPropertyInfo), '("accessibleTableCaptionObject", Atk.Object.ObjectAccessibleTableCaptionObjectPropertyInfo), '("accessibleTableColumnDescription", Atk.Object.ObjectAccessibleTableColumnDescriptionPropertyInfo), '("accessibleTableColumnHeader", Atk.Object.ObjectAccessibleTableColumnHeaderPropertyInfo), '("accessibleTableRowDescription", Atk.Object.ObjectAccessibleTableRowDescriptionPropertyInfo), '("accessibleTableRowHeader", Atk.Object.ObjectAccessibleTableRowHeaderPropertyInfo), '("accessibleTableSummary", Atk.Object.ObjectAccessibleTableSummaryPropertyInfo), '("accessibleValue", Atk.Object.ObjectAccessibleValuePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTableCellMethod (t :: Symbol) (o :: *) :: * where
    ResolveTableCellMethod "addRelationship" o = Atk.Object.ObjectAddRelationshipMethodInfo
    ResolveTableCellMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTableCellMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTableCellMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTableCellMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTableCellMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTableCellMethod "initialize" o = Atk.Object.ObjectInitializeMethodInfo
    ResolveTableCellMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTableCellMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTableCellMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTableCellMethod "notifyStateChange" o = Atk.Object.ObjectNotifyStateChangeMethodInfo
    ResolveTableCellMethod "peekParent" o = Atk.Object.ObjectPeekParentMethodInfo
    ResolveTableCellMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTableCellMethod "refAccessibleChild" o = Atk.Object.ObjectRefAccessibleChildMethodInfo
    ResolveTableCellMethod "refRelationSet" o = Atk.Object.ObjectRefRelationSetMethodInfo
    ResolveTableCellMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTableCellMethod "refStateSet" o = Atk.Object.ObjectRefStateSetMethodInfo
    ResolveTableCellMethod "removePropertyChangeHandler" o = Atk.Object.ObjectRemovePropertyChangeHandlerMethodInfo
    ResolveTableCellMethod "removeRelationship" o = Atk.Object.ObjectRemoveRelationshipMethodInfo
    ResolveTableCellMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTableCellMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTableCellMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTableCellMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTableCellMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTableCellMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTableCellMethod "getAttributes" o = Atk.Object.ObjectGetAttributesMethodInfo
    ResolveTableCellMethod "getColumnHeaderCells" o = TableCellGetColumnHeaderCellsMethodInfo
    ResolveTableCellMethod "getColumnSpan" o = TableCellGetColumnSpanMethodInfo
    ResolveTableCellMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTableCellMethod "getDescription" o = Atk.Object.ObjectGetDescriptionMethodInfo
    ResolveTableCellMethod "getIndexInParent" o = Atk.Object.ObjectGetIndexInParentMethodInfo
    ResolveTableCellMethod "getLayer" o = Atk.Object.ObjectGetLayerMethodInfo
    ResolveTableCellMethod "getMdiZorder" o = Atk.Object.ObjectGetMdiZorderMethodInfo
    ResolveTableCellMethod "getNAccessibleChildren" o = Atk.Object.ObjectGetNAccessibleChildrenMethodInfo
    ResolveTableCellMethod "getName" o = Atk.Object.ObjectGetNameMethodInfo
    ResolveTableCellMethod "getObjectLocale" o = Atk.Object.ObjectGetObjectLocaleMethodInfo
    ResolveTableCellMethod "getParent" o = Atk.Object.ObjectGetParentMethodInfo
    ResolveTableCellMethod "getPosition" o = TableCellGetPositionMethodInfo
    ResolveTableCellMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTableCellMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTableCellMethod "getRole" o = Atk.Object.ObjectGetRoleMethodInfo
    ResolveTableCellMethod "getRowColumnSpan" o = TableCellGetRowColumnSpanMethodInfo
    ResolveTableCellMethod "getRowHeaderCells" o = TableCellGetRowHeaderCellsMethodInfo
    ResolveTableCellMethod "getRowSpan" o = TableCellGetRowSpanMethodInfo
    ResolveTableCellMethod "getTable" o = TableCellGetTableMethodInfo
    ResolveTableCellMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTableCellMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTableCellMethod "setDescription" o = Atk.Object.ObjectSetDescriptionMethodInfo
    ResolveTableCellMethod "setName" o = Atk.Object.ObjectSetNameMethodInfo
    ResolveTableCellMethod "setParent" o = Atk.Object.ObjectSetParentMethodInfo
    ResolveTableCellMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTableCellMethod "setRole" o = Atk.Object.ObjectSetRoleMethodInfo
    ResolveTableCellMethod l o = O.MethodResolutionFailed l o

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

#endif

-- method TableCell::get_column_header_cells
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TableCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a GObject instance that implements AtkTableCellIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TPtrArray
--                  (TInterface Name { namespace = "Atk" , name = "Object" }))
-- throws : False
-- Skip return : False

foreign import ccall "atk_table_cell_get_column_header_cells" atk_table_cell_get_column_header_cells :: 
    Ptr TableCell ->                        -- cell : TInterface (Name {namespace = "Atk", name = "TableCell"})
    IO (Ptr (GPtrArray (Ptr Atk.Object.Object)))

-- | Returns the column headers as an array of cell accessibles.
-- 
-- /Since: 2.12/
tableCellGetColumnHeaderCells ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableCell a) =>
    a
    -- ^ /@cell@/: a GObject instance that implements AtkTableCellIface
    -> m [Atk.Object.Object]
    -- ^ __Returns:__ a GPtrArray of AtkObjects
    -- representing the column header cells.
tableCellGetColumnHeaderCells :: a -> m [Object]
tableCellGetColumnHeaderCells cell :: a
cell = IO [Object] -> m [Object]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Object] -> m [Object]) -> IO [Object] -> m [Object]
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableCell
cell' <- a -> IO (Ptr TableCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cell
    Ptr (GPtrArray (Ptr Object))
result <- Ptr TableCell -> IO (Ptr (GPtrArray (Ptr Object)))
atk_table_cell_get_column_header_cells Ptr TableCell
cell'
    Text -> Ptr (GPtrArray (Ptr Object)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "tableCellGetColumnHeaderCells" Ptr (GPtrArray (Ptr Object))
result
    [Ptr Object]
result' <- Ptr (GPtrArray (Ptr Object)) -> IO [Ptr Object]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr Object))
result
    [Object]
result'' <- (Ptr Object -> IO Object) -> [Ptr Object] -> IO [Object]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
Atk.Object.Object) [Ptr Object]
result'
    Ptr (GPtrArray (Ptr Object)) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray (Ptr Object))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cell
    [Object] -> IO [Object]
forall (m :: * -> *) a. Monad m => a -> m a
return [Object]
result''

#if defined(ENABLE_OVERLOADING)
data TableCellGetColumnHeaderCellsMethodInfo
instance (signature ~ (m [Atk.Object.Object]), MonadIO m, IsTableCell a) => O.MethodInfo TableCellGetColumnHeaderCellsMethodInfo a signature where
    overloadedMethod = tableCellGetColumnHeaderCells

#endif

-- method TableCell::get_column_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TableCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a GObject instance that implements AtkTableCellIface"
--                 , 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 "atk_table_cell_get_column_span" atk_table_cell_get_column_span :: 
    Ptr TableCell ->                        -- cell : TInterface (Name {namespace = "Atk", name = "TableCell"})
    IO Int32

-- | Returns the number of columns occupied by this cell accessible.
-- 
-- /Since: 2.12/
tableCellGetColumnSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableCell a) =>
    a
    -- ^ /@cell@/: a GObject instance that implements AtkTableCellIface
    -> m Int32
    -- ^ __Returns:__ a gint representing the number of columns occupied by this cell,
    -- or 0 if the cell does not implement this method.
tableCellGetColumnSpan :: a -> m Int32
tableCellGetColumnSpan cell :: a
cell = 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 TableCell
cell' <- a -> IO (Ptr TableCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cell
    Int32
result <- Ptr TableCell -> IO Int32
atk_table_cell_get_column_span Ptr TableCell
cell'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cell
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TableCellGetColumnSpanMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTableCell a) => O.MethodInfo TableCellGetColumnSpanMethodInfo a signature where
    overloadedMethod = tableCellGetColumnSpan

#endif

-- method TableCell::get_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TableCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a GObject instance that implements AtkTableCellIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "row"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the row of the given cell."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "column"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the column of the given cell."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_table_cell_get_position" atk_table_cell_get_position :: 
    Ptr TableCell ->                        -- cell : TInterface (Name {namespace = "Atk", name = "TableCell"})
    Ptr Int32 ->                            -- row : TBasicType TInt
    Ptr Int32 ->                            -- column : TBasicType TInt
    IO CInt

-- | Retrieves the tabular position of this cell.
-- 
-- /Since: 2.12/
tableCellGetPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableCell a) =>
    a
    -- ^ /@cell@/: a GObject instance that implements AtkTableCellIface
    -> m ((Bool, Int32, Int32))
    -- ^ __Returns:__ TRUE if successful; FALSE otherwise.
tableCellGetPosition :: a -> m (Bool, Int32, Int32)
tableCellGetPosition cell :: a
cell = IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32))
-> IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableCell
cell' <- a -> IO (Ptr TableCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cell
    Ptr Int32
row <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
column <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr TableCell -> Ptr Int32 -> Ptr Int32 -> IO CInt
atk_table_cell_get_position Ptr TableCell
cell' Ptr Int32
row Ptr Int32
column
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Int32
row' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
row
    Int32
column' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
column
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cell
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
row
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
column
    (Bool, Int32, Int32) -> IO (Bool, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Int32
row', Int32
column')

#if defined(ENABLE_OVERLOADING)
data TableCellGetPositionMethodInfo
instance (signature ~ (m ((Bool, Int32, Int32))), MonadIO m, IsTableCell a) => O.MethodInfo TableCellGetPositionMethodInfo a signature where
    overloadedMethod = tableCellGetPosition

#endif

-- method TableCell::get_row_column_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TableCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a GObject instance that implements AtkTableCellIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "row"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the row index of the given cell."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "column"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the column index of the given cell."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "row_span"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of rows occupied by this cell."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "column_span"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of columns occupied by this cell."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_table_cell_get_row_column_span" atk_table_cell_get_row_column_span :: 
    Ptr TableCell ->                        -- cell : TInterface (Name {namespace = "Atk", name = "TableCell"})
    Ptr Int32 ->                            -- row : TBasicType TInt
    Ptr Int32 ->                            -- column : TBasicType TInt
    Ptr Int32 ->                            -- row_span : TBasicType TInt
    Ptr Int32 ->                            -- column_span : TBasicType TInt
    IO CInt

-- | Gets the row and column indexes and span of this cell accessible.
-- 
-- Note: If the object does not implement this function, then, by default, atk
-- will implement this function by calling get_row_span and get_column_span
-- on the object.
-- 
-- /Since: 2.12/
tableCellGetRowColumnSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableCell a) =>
    a
    -- ^ /@cell@/: a GObject instance that implements AtkTableCellIface
    -> m ((Bool, Int32, Int32, Int32, Int32))
    -- ^ __Returns:__ TRUE if successful; FALSE otherwise.
tableCellGetRowColumnSpan :: a -> m (Bool, Int32, Int32, Int32, Int32)
tableCellGetRowColumnSpan cell :: a
cell = IO (Bool, Int32, Int32, Int32, Int32)
-> m (Bool, Int32, Int32, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Int32, Int32, Int32, Int32)
 -> m (Bool, Int32, Int32, Int32, Int32))
-> IO (Bool, Int32, Int32, Int32, Int32)
-> m (Bool, Int32, Int32, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableCell
cell' <- a -> IO (Ptr TableCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cell
    Ptr Int32
row <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
column <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
rowSpan <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
columnSpan <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr TableCell
-> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> IO CInt
atk_table_cell_get_row_column_span Ptr TableCell
cell' Ptr Int32
row Ptr Int32
column Ptr Int32
rowSpan Ptr Int32
columnSpan
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Int32
row' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
row
    Int32
column' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
column
    Int32
rowSpan' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
rowSpan
    Int32
columnSpan' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
columnSpan
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cell
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
row
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
column
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
rowSpan
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
columnSpan
    (Bool, Int32, Int32, Int32, Int32)
-> IO (Bool, Int32, Int32, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Int32
row', Int32
column', Int32
rowSpan', Int32
columnSpan')

#if defined(ENABLE_OVERLOADING)
data TableCellGetRowColumnSpanMethodInfo
instance (signature ~ (m ((Bool, Int32, Int32, Int32, Int32))), MonadIO m, IsTableCell a) => O.MethodInfo TableCellGetRowColumnSpanMethodInfo a signature where
    overloadedMethod = tableCellGetRowColumnSpan

#endif

-- method TableCell::get_row_header_cells
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TableCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a GObject instance that implements AtkTableCellIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TPtrArray
--                  (TInterface Name { namespace = "Atk" , name = "Object" }))
-- throws : False
-- Skip return : False

foreign import ccall "atk_table_cell_get_row_header_cells" atk_table_cell_get_row_header_cells :: 
    Ptr TableCell ->                        -- cell : TInterface (Name {namespace = "Atk", name = "TableCell"})
    IO (Ptr (GPtrArray (Ptr Atk.Object.Object)))

-- | Returns the row headers as an array of cell accessibles.
-- 
-- /Since: 2.12/
tableCellGetRowHeaderCells ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableCell a) =>
    a
    -- ^ /@cell@/: a GObject instance that implements AtkTableCellIface
    -> m [Atk.Object.Object]
    -- ^ __Returns:__ a GPtrArray of AtkObjects
    -- representing the row header cells.
tableCellGetRowHeaderCells :: a -> m [Object]
tableCellGetRowHeaderCells cell :: a
cell = IO [Object] -> m [Object]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Object] -> m [Object]) -> IO [Object] -> m [Object]
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableCell
cell' <- a -> IO (Ptr TableCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cell
    Ptr (GPtrArray (Ptr Object))
result <- Ptr TableCell -> IO (Ptr (GPtrArray (Ptr Object)))
atk_table_cell_get_row_header_cells Ptr TableCell
cell'
    Text -> Ptr (GPtrArray (Ptr Object)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "tableCellGetRowHeaderCells" Ptr (GPtrArray (Ptr Object))
result
    [Ptr Object]
result' <- Ptr (GPtrArray (Ptr Object)) -> IO [Ptr Object]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr Object))
result
    [Object]
result'' <- (Ptr Object -> IO Object) -> [Ptr Object] -> IO [Object]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
Atk.Object.Object) [Ptr Object]
result'
    Ptr (GPtrArray (Ptr Object)) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray (Ptr Object))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cell
    [Object] -> IO [Object]
forall (m :: * -> *) a. Monad m => a -> m a
return [Object]
result''

#if defined(ENABLE_OVERLOADING)
data TableCellGetRowHeaderCellsMethodInfo
instance (signature ~ (m [Atk.Object.Object]), MonadIO m, IsTableCell a) => O.MethodInfo TableCellGetRowHeaderCellsMethodInfo a signature where
    overloadedMethod = tableCellGetRowHeaderCells

#endif

-- method TableCell::get_row_span
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TableCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a GObject instance that implements AtkTableCellIface"
--                 , 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 "atk_table_cell_get_row_span" atk_table_cell_get_row_span :: 
    Ptr TableCell ->                        -- cell : TInterface (Name {namespace = "Atk", name = "TableCell"})
    IO Int32

-- | Returns the number of rows occupied by this cell accessible.
-- 
-- /Since: 2.12/
tableCellGetRowSpan ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableCell a) =>
    a
    -- ^ /@cell@/: a GObject instance that implements AtkTableCellIface
    -> m Int32
    -- ^ __Returns:__ a gint representing the number of rows occupied by this cell,
    -- or 0 if the cell does not implement this method.
tableCellGetRowSpan :: a -> m Int32
tableCellGetRowSpan cell :: a
cell = 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 TableCell
cell' <- a -> IO (Ptr TableCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cell
    Int32
result <- Ptr TableCell -> IO Int32
atk_table_cell_get_row_span Ptr TableCell
cell'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cell
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TableCellGetRowSpanMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTableCell a) => O.MethodInfo TableCellGetRowSpanMethodInfo a signature where
    overloadedMethod = tableCellGetRowSpan

#endif

-- method TableCell::get_table
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "cell"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "TableCell" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a GObject instance that implements AtkTableCellIface"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_table_cell_get_table" atk_table_cell_get_table :: 
    Ptr TableCell ->                        -- cell : TInterface (Name {namespace = "Atk", name = "TableCell"})
    IO (Ptr Atk.Object.Object)

-- | Returns a reference to the accessible of the containing table.
-- 
-- /Since: 2.12/
tableCellGetTable ::
    (B.CallStack.HasCallStack, MonadIO m, IsTableCell a) =>
    a
    -- ^ /@cell@/: a GObject instance that implements AtkTableCellIface
    -> m Atk.Object.Object
    -- ^ __Returns:__ the atk object for the containing table.
tableCellGetTable :: a -> m Object
tableCellGetTable cell :: a
cell = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
    Ptr TableCell
cell' <- a -> IO (Ptr TableCell)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
cell
    Ptr Object
result <- Ptr TableCell -> IO (Ptr Object)
atk_table_cell_get_table Ptr TableCell
cell'
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "tableCellGetTable" Ptr Object
result
    Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
Atk.Object.Object) Ptr Object
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
cell
    Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data TableCellGetTableMethodInfo
instance (signature ~ (m Atk.Object.Object), MonadIO m, IsTableCell a) => O.MethodInfo TableCellGetTableMethodInfo a signature where
    overloadedMethod = tableCellGetTable

#endif