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

module GI.Gtk.Objects.CellArea
    ( 

-- * Exported types
    CellArea(..)                            ,
    CellAreaK                               ,
    toCellArea                              ,
    noCellArea                              ,


 -- * Methods
-- ** cellAreaActivate
    cellAreaActivate                        ,


-- ** cellAreaActivateCell
    cellAreaActivateCell                    ,


-- ** cellAreaAdd
    cellAreaAdd                             ,


-- ** cellAreaAddFocusSibling
    cellAreaAddFocusSibling                 ,


-- ** cellAreaApplyAttributes
    cellAreaApplyAttributes                 ,


-- ** cellAreaAttributeConnect
    cellAreaAttributeConnect                ,


-- ** cellAreaAttributeDisconnect
    cellAreaAttributeDisconnect             ,


-- ** cellAreaAttributeGetColumn
    cellAreaAttributeGetColumn              ,


-- ** cellAreaCellGetProperty
    cellAreaCellGetProperty                 ,


-- ** cellAreaCellSetProperty
    cellAreaCellSetProperty                 ,


-- ** cellAreaCopyContext
    cellAreaCopyContext                     ,


-- ** cellAreaCreateContext
    cellAreaCreateContext                   ,


-- ** cellAreaEvent
    cellAreaEvent                           ,


-- ** cellAreaFocus
    cellAreaFocus                           ,


-- ** cellAreaForeach
    cellAreaForeach                         ,


-- ** cellAreaForeachAlloc
    cellAreaForeachAlloc                    ,


-- ** cellAreaGetCellAllocation
    cellAreaGetCellAllocation               ,


-- ** cellAreaGetCellAtPosition
    cellAreaGetCellAtPosition               ,


-- ** cellAreaGetCurrentPathString
    cellAreaGetCurrentPathString            ,


-- ** cellAreaGetEditWidget
    cellAreaGetEditWidget                   ,


-- ** cellAreaGetEditedCell
    cellAreaGetEditedCell                   ,


-- ** cellAreaGetFocusCell
    cellAreaGetFocusCell                    ,


-- ** cellAreaGetFocusFromSibling
    cellAreaGetFocusFromSibling             ,


-- ** cellAreaGetFocusSiblings
    cellAreaGetFocusSiblings                ,


-- ** cellAreaGetPreferredHeight
    cellAreaGetPreferredHeight              ,


-- ** cellAreaGetPreferredHeightForWidth
    cellAreaGetPreferredHeightForWidth      ,


-- ** cellAreaGetPreferredWidth
    cellAreaGetPreferredWidth               ,


-- ** cellAreaGetPreferredWidthForHeight
    cellAreaGetPreferredWidthForHeight      ,


-- ** cellAreaGetRequestMode
    cellAreaGetRequestMode                  ,


-- ** cellAreaHasRenderer
    cellAreaHasRenderer                     ,


-- ** cellAreaInnerCellArea
    cellAreaInnerCellArea                   ,


-- ** cellAreaIsActivatable
    cellAreaIsActivatable                   ,


-- ** cellAreaIsFocusSibling
    cellAreaIsFocusSibling                  ,


-- ** cellAreaRemove
    cellAreaRemove                          ,


-- ** cellAreaRemoveFocusSibling
    cellAreaRemoveFocusSibling              ,


-- ** cellAreaRender
    cellAreaRender                          ,


-- ** cellAreaRequestRenderer
    cellAreaRequestRenderer                 ,


-- ** cellAreaSetFocusCell
    cellAreaSetFocusCell                    ,


-- ** cellAreaStopEditing
    cellAreaStopEditing                     ,




 -- * Properties
-- ** EditWidget
    CellAreaEditWidgetPropertyInfo          ,
    getCellAreaEditWidget                   ,


-- ** EditedCell
    CellAreaEditedCellPropertyInfo          ,
    getCellAreaEditedCell                   ,


-- ** FocusCell
    CellAreaFocusCellPropertyInfo           ,
    constructCellAreaFocusCell              ,
    getCellAreaFocusCell                    ,
    setCellAreaFocusCell                    ,




 -- * Signals
-- ** AddEditable
    CellAreaAddEditableCallback             ,
    CellAreaAddEditableCallbackC            ,
    CellAreaAddEditableSignalInfo           ,
    afterCellAreaAddEditable                ,
    cellAreaAddEditableCallbackWrapper      ,
    cellAreaAddEditableClosure              ,
    mkCellAreaAddEditableCallback           ,
    noCellAreaAddEditableCallback           ,
    onCellAreaAddEditable                   ,


-- ** ApplyAttributes
    CellAreaApplyAttributesCallback         ,
    CellAreaApplyAttributesCallbackC        ,
    CellAreaApplyAttributesSignalInfo       ,
    afterCellAreaApplyAttributes            ,
    cellAreaApplyAttributesCallbackWrapper  ,
    cellAreaApplyAttributesClosure          ,
    mkCellAreaApplyAttributesCallback       ,
    noCellAreaApplyAttributesCallback       ,
    onCellAreaApplyAttributes               ,


-- ** FocusChanged
    CellAreaFocusChangedCallback            ,
    CellAreaFocusChangedCallbackC           ,
    CellAreaFocusChangedSignalInfo          ,
    afterCellAreaFocusChanged               ,
    cellAreaFocusChangedCallbackWrapper     ,
    cellAreaFocusChangedClosure             ,
    mkCellAreaFocusChangedCallback          ,
    noCellAreaFocusChangedCallback          ,
    onCellAreaFocusChanged                  ,


-- ** RemoveEditable
    CellAreaRemoveEditableCallback          ,
    CellAreaRemoveEditableCallbackC         ,
    CellAreaRemoveEditableSignalInfo        ,
    afterCellAreaRemoveEditable             ,
    cellAreaRemoveEditableCallbackWrapper   ,
    cellAreaRemoveEditableClosure           ,
    mkCellAreaRemoveEditableCallback        ,
    noCellAreaRemoveEditableCallback        ,
    onCellAreaRemoveEditable                ,




    ) where

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

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

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

newtype CellArea = CellArea (ForeignPtr CellArea)
foreign import ccall "gtk_cell_area_get_type"
    c_gtk_cell_area_get_type :: IO GType

type instance ParentTypes CellArea = CellAreaParentTypes
type CellAreaParentTypes = '[GObject.Object, Buildable, CellLayout]

instance GObject CellArea where
    gobjectIsInitiallyUnowned _ = True
    gobjectType _ = c_gtk_cell_area_get_type
    

class GObject o => CellAreaK o
instance (GObject o, IsDescendantOf CellArea o) => CellAreaK o

toCellArea :: CellAreaK o => o -> IO CellArea
toCellArea = unsafeCastTo CellArea

noCellArea :: Maybe CellArea
noCellArea = Nothing

-- signal CellArea::add-editable
type CellAreaAddEditableCallback =
    CellRenderer ->
    CellEditable ->
    Cairo.RectangleInt ->
    T.Text ->
    IO ()

noCellAreaAddEditableCallback :: Maybe CellAreaAddEditableCallback
noCellAreaAddEditableCallback = Nothing

type CellAreaAddEditableCallbackC =
    Ptr () ->                               -- object
    Ptr CellRenderer ->
    Ptr CellEditable ->
    Ptr Cairo.RectangleInt ->
    CString ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkCellAreaAddEditableCallback :: CellAreaAddEditableCallbackC -> IO (FunPtr CellAreaAddEditableCallbackC)

cellAreaAddEditableClosure :: CellAreaAddEditableCallback -> IO Closure
cellAreaAddEditableClosure cb = newCClosure =<< mkCellAreaAddEditableCallback wrapped
    where wrapped = cellAreaAddEditableCallbackWrapper cb

cellAreaAddEditableCallbackWrapper ::
    CellAreaAddEditableCallback ->
    Ptr () ->
    Ptr CellRenderer ->
    Ptr CellEditable ->
    Ptr Cairo.RectangleInt ->
    CString ->
    Ptr () ->
    IO ()
cellAreaAddEditableCallbackWrapper _cb _ renderer editable cell_area path _ = do
    renderer' <- (newObject CellRenderer) renderer
    editable' <- (newObject CellEditable) editable
    cell_area' <- (newBoxed Cairo.RectangleInt) cell_area
    path' <- cstringToText path
    _cb  renderer' editable' cell_area' path'

onCellAreaAddEditable :: (GObject a, MonadIO m) => a -> CellAreaAddEditableCallback -> m SignalHandlerId
onCellAreaAddEditable obj cb = liftIO $ connectCellAreaAddEditable obj cb SignalConnectBefore
afterCellAreaAddEditable :: (GObject a, MonadIO m) => a -> CellAreaAddEditableCallback -> m SignalHandlerId
afterCellAreaAddEditable obj cb = connectCellAreaAddEditable obj cb SignalConnectAfter

connectCellAreaAddEditable :: (GObject a, MonadIO m) =>
                              a -> CellAreaAddEditableCallback -> SignalConnectMode -> m SignalHandlerId
connectCellAreaAddEditable obj cb after = liftIO $ do
    cb' <- mkCellAreaAddEditableCallback (cellAreaAddEditableCallbackWrapper cb)
    connectSignalFunPtr obj "add-editable" cb' after

-- signal CellArea::apply-attributes
type CellAreaApplyAttributesCallback =
    TreeModel ->
    TreeIter ->
    Bool ->
    Bool ->
    IO ()

noCellAreaApplyAttributesCallback :: Maybe CellAreaApplyAttributesCallback
noCellAreaApplyAttributesCallback = Nothing

type CellAreaApplyAttributesCallbackC =
    Ptr () ->                               -- object
    Ptr TreeModel ->
    Ptr TreeIter ->
    CInt ->
    CInt ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkCellAreaApplyAttributesCallback :: CellAreaApplyAttributesCallbackC -> IO (FunPtr CellAreaApplyAttributesCallbackC)

cellAreaApplyAttributesClosure :: CellAreaApplyAttributesCallback -> IO Closure
cellAreaApplyAttributesClosure cb = newCClosure =<< mkCellAreaApplyAttributesCallback wrapped
    where wrapped = cellAreaApplyAttributesCallbackWrapper cb

cellAreaApplyAttributesCallbackWrapper ::
    CellAreaApplyAttributesCallback ->
    Ptr () ->
    Ptr TreeModel ->
    Ptr TreeIter ->
    CInt ->
    CInt ->
    Ptr () ->
    IO ()
cellAreaApplyAttributesCallbackWrapper _cb _ model iter is_expander is_expanded _ = do
    model' <- (newObject TreeModel) model
    iter' <- (newBoxed TreeIter) iter
    let is_expander' = (/= 0) is_expander
    let is_expanded' = (/= 0) is_expanded
    _cb  model' iter' is_expander' is_expanded'

onCellAreaApplyAttributes :: (GObject a, MonadIO m) => a -> CellAreaApplyAttributesCallback -> m SignalHandlerId
onCellAreaApplyAttributes obj cb = liftIO $ connectCellAreaApplyAttributes obj cb SignalConnectBefore
afterCellAreaApplyAttributes :: (GObject a, MonadIO m) => a -> CellAreaApplyAttributesCallback -> m SignalHandlerId
afterCellAreaApplyAttributes obj cb = connectCellAreaApplyAttributes obj cb SignalConnectAfter

connectCellAreaApplyAttributes :: (GObject a, MonadIO m) =>
                                  a -> CellAreaApplyAttributesCallback -> SignalConnectMode -> m SignalHandlerId
connectCellAreaApplyAttributes obj cb after = liftIO $ do
    cb' <- mkCellAreaApplyAttributesCallback (cellAreaApplyAttributesCallbackWrapper cb)
    connectSignalFunPtr obj "apply-attributes" cb' after

-- signal CellArea::focus-changed
type CellAreaFocusChangedCallback =
    CellRenderer ->
    T.Text ->
    IO ()

noCellAreaFocusChangedCallback :: Maybe CellAreaFocusChangedCallback
noCellAreaFocusChangedCallback = Nothing

type CellAreaFocusChangedCallbackC =
    Ptr () ->                               -- object
    Ptr CellRenderer ->
    CString ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkCellAreaFocusChangedCallback :: CellAreaFocusChangedCallbackC -> IO (FunPtr CellAreaFocusChangedCallbackC)

cellAreaFocusChangedClosure :: CellAreaFocusChangedCallback -> IO Closure
cellAreaFocusChangedClosure cb = newCClosure =<< mkCellAreaFocusChangedCallback wrapped
    where wrapped = cellAreaFocusChangedCallbackWrapper cb

cellAreaFocusChangedCallbackWrapper ::
    CellAreaFocusChangedCallback ->
    Ptr () ->
    Ptr CellRenderer ->
    CString ->
    Ptr () ->
    IO ()
cellAreaFocusChangedCallbackWrapper _cb _ renderer path _ = do
    renderer' <- (newObject CellRenderer) renderer
    path' <- cstringToText path
    _cb  renderer' path'

onCellAreaFocusChanged :: (GObject a, MonadIO m) => a -> CellAreaFocusChangedCallback -> m SignalHandlerId
onCellAreaFocusChanged obj cb = liftIO $ connectCellAreaFocusChanged obj cb SignalConnectBefore
afterCellAreaFocusChanged :: (GObject a, MonadIO m) => a -> CellAreaFocusChangedCallback -> m SignalHandlerId
afterCellAreaFocusChanged obj cb = connectCellAreaFocusChanged obj cb SignalConnectAfter

connectCellAreaFocusChanged :: (GObject a, MonadIO m) =>
                               a -> CellAreaFocusChangedCallback -> SignalConnectMode -> m SignalHandlerId
connectCellAreaFocusChanged obj cb after = liftIO $ do
    cb' <- mkCellAreaFocusChangedCallback (cellAreaFocusChangedCallbackWrapper cb)
    connectSignalFunPtr obj "focus-changed" cb' after

-- signal CellArea::remove-editable
type CellAreaRemoveEditableCallback =
    CellRenderer ->
    CellEditable ->
    IO ()

noCellAreaRemoveEditableCallback :: Maybe CellAreaRemoveEditableCallback
noCellAreaRemoveEditableCallback = Nothing

type CellAreaRemoveEditableCallbackC =
    Ptr () ->                               -- object
    Ptr CellRenderer ->
    Ptr CellEditable ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkCellAreaRemoveEditableCallback :: CellAreaRemoveEditableCallbackC -> IO (FunPtr CellAreaRemoveEditableCallbackC)

cellAreaRemoveEditableClosure :: CellAreaRemoveEditableCallback -> IO Closure
cellAreaRemoveEditableClosure cb = newCClosure =<< mkCellAreaRemoveEditableCallback wrapped
    where wrapped = cellAreaRemoveEditableCallbackWrapper cb

cellAreaRemoveEditableCallbackWrapper ::
    CellAreaRemoveEditableCallback ->
    Ptr () ->
    Ptr CellRenderer ->
    Ptr CellEditable ->
    Ptr () ->
    IO ()
cellAreaRemoveEditableCallbackWrapper _cb _ renderer editable _ = do
    renderer' <- (newObject CellRenderer) renderer
    editable' <- (newObject CellEditable) editable
    _cb  renderer' editable'

onCellAreaRemoveEditable :: (GObject a, MonadIO m) => a -> CellAreaRemoveEditableCallback -> m SignalHandlerId
onCellAreaRemoveEditable obj cb = liftIO $ connectCellAreaRemoveEditable obj cb SignalConnectBefore
afterCellAreaRemoveEditable :: (GObject a, MonadIO m) => a -> CellAreaRemoveEditableCallback -> m SignalHandlerId
afterCellAreaRemoveEditable obj cb = connectCellAreaRemoveEditable obj cb SignalConnectAfter

connectCellAreaRemoveEditable :: (GObject a, MonadIO m) =>
                                 a -> CellAreaRemoveEditableCallback -> SignalConnectMode -> m SignalHandlerId
connectCellAreaRemoveEditable obj cb after = liftIO $ do
    cb' <- mkCellAreaRemoveEditableCallback (cellAreaRemoveEditableCallbackWrapper cb)
    connectSignalFunPtr obj "remove-editable" cb' after

-- VVV Prop "edit-widget"
   -- Type: TInterface "Gtk" "CellEditable"
   -- Flags: [PropertyReadable]

getCellAreaEditWidget :: (MonadIO m, CellAreaK o) => o -> m CellEditable
getCellAreaEditWidget obj = liftIO $ getObjectPropertyObject obj "edit-widget" CellEditable

data CellAreaEditWidgetPropertyInfo
instance AttrInfo CellAreaEditWidgetPropertyInfo where
    type AttrAllowedOps CellAreaEditWidgetPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint CellAreaEditWidgetPropertyInfo = (~) ()
    type AttrBaseTypeConstraint CellAreaEditWidgetPropertyInfo = CellAreaK
    type AttrGetType CellAreaEditWidgetPropertyInfo = CellEditable
    type AttrLabel CellAreaEditWidgetPropertyInfo = "CellArea::edit-widget"
    attrGet _ = getCellAreaEditWidget
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "edited-cell"
   -- Type: TInterface "Gtk" "CellRenderer"
   -- Flags: [PropertyReadable]

getCellAreaEditedCell :: (MonadIO m, CellAreaK o) => o -> m CellRenderer
getCellAreaEditedCell obj = liftIO $ getObjectPropertyObject obj "edited-cell" CellRenderer

data CellAreaEditedCellPropertyInfo
instance AttrInfo CellAreaEditedCellPropertyInfo where
    type AttrAllowedOps CellAreaEditedCellPropertyInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint CellAreaEditedCellPropertyInfo = (~) ()
    type AttrBaseTypeConstraint CellAreaEditedCellPropertyInfo = CellAreaK
    type AttrGetType CellAreaEditedCellPropertyInfo = CellRenderer
    type AttrLabel CellAreaEditedCellPropertyInfo = "CellArea::edited-cell"
    attrGet _ = getCellAreaEditedCell
    attrSet _ = undefined
    attrConstruct _ = undefined

-- VVV Prop "focus-cell"
   -- Type: TInterface "Gtk" "CellRenderer"
   -- Flags: [PropertyReadable,PropertyWritable]

getCellAreaFocusCell :: (MonadIO m, CellAreaK o) => o -> m CellRenderer
getCellAreaFocusCell obj = liftIO $ getObjectPropertyObject obj "focus-cell" CellRenderer

setCellAreaFocusCell :: (MonadIO m, CellAreaK o, CellRendererK a) => o -> a -> m ()
setCellAreaFocusCell obj val = liftIO $ setObjectPropertyObject obj "focus-cell" val

constructCellAreaFocusCell :: (CellRendererK a) => a -> IO ([Char], GValue)
constructCellAreaFocusCell val = constructObjectPropertyObject "focus-cell" val

data CellAreaFocusCellPropertyInfo
instance AttrInfo CellAreaFocusCellPropertyInfo where
    type AttrAllowedOps CellAreaFocusCellPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint CellAreaFocusCellPropertyInfo = CellRendererK
    type AttrBaseTypeConstraint CellAreaFocusCellPropertyInfo = CellAreaK
    type AttrGetType CellAreaFocusCellPropertyInfo = CellRenderer
    type AttrLabel CellAreaFocusCellPropertyInfo = "CellArea::focus-cell"
    attrGet _ = getCellAreaFocusCell
    attrSet _ = setCellAreaFocusCell
    attrConstruct _ = constructCellAreaFocusCell

type instance AttributeList CellArea = CellAreaAttributeList
type CellAreaAttributeList = ('[ '("edit-widget", CellAreaEditWidgetPropertyInfo), '("edited-cell", CellAreaEditedCellPropertyInfo), '("focus-cell", CellAreaFocusCellPropertyInfo)] :: [(Symbol, *)])

data CellAreaAddEditableSignalInfo
instance SignalInfo CellAreaAddEditableSignalInfo where
    type HaskellCallbackType CellAreaAddEditableSignalInfo = CellAreaAddEditableCallback
    connectSignal _ = connectCellAreaAddEditable

data CellAreaApplyAttributesSignalInfo
instance SignalInfo CellAreaApplyAttributesSignalInfo where
    type HaskellCallbackType CellAreaApplyAttributesSignalInfo = CellAreaApplyAttributesCallback
    connectSignal _ = connectCellAreaApplyAttributes

data CellAreaFocusChangedSignalInfo
instance SignalInfo CellAreaFocusChangedSignalInfo where
    type HaskellCallbackType CellAreaFocusChangedSignalInfo = CellAreaFocusChangedCallback
    connectSignal _ = connectCellAreaFocusChanged

data CellAreaRemoveEditableSignalInfo
instance SignalInfo CellAreaRemoveEditableSignalInfo where
    type HaskellCallbackType CellAreaRemoveEditableSignalInfo = CellAreaRemoveEditableCallback
    connectSignal _ = connectCellAreaRemoveEditable

type instance SignalList CellArea = CellAreaSignalList
type CellAreaSignalList = ('[ '("add-editable", CellAreaAddEditableSignalInfo), '("apply-attributes", CellAreaApplyAttributesSignalInfo), '("focus-changed", CellAreaFocusChangedSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("remove-editable", CellAreaRemoveEditableSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method CellArea::activate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gtk" "CellRendererState", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "edit_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gtk" "CellRendererState", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "edit_only", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_activate" gtk_cell_area_activate :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr Cairo.RectangleInt ->               -- cell_area : TInterface "cairo" "RectangleInt"
    CUInt ->                                -- flags : TInterface "Gtk" "CellRendererState"
    CInt ->                                 -- edit_only : TBasicType TBoolean
    IO CInt


cellAreaActivate ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    Cairo.RectangleInt ->                   -- cell_area
    [CellRendererState] ->                  -- flags
    Bool ->                                 -- edit_only
    m Bool
cellAreaActivate _obj context widget cell_area flags edit_only = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    let cell_area' = unsafeManagedPtrGetPtr cell_area
    let flags' = gflagsToWord flags
    let edit_only' = (fromIntegral . fromEnum) edit_only
    result <- gtk_cell_area_activate _obj' context' widget' cell_area' flags' edit_only'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    touchManagedPtr cell_area
    return result'

-- method CellArea::activate_cell
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "event", argType = TInterface "Gdk" "Event", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gtk" "CellRendererState", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "event", argType = TInterface "Gdk" "Event", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gtk" "CellRendererState", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_activate_cell" gtk_cell_area_activate_cell :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    Ptr Gdk.Event ->                        -- event : TInterface "Gdk" "Event"
    Ptr Cairo.RectangleInt ->               -- cell_area : TInterface "cairo" "RectangleInt"
    CUInt ->                                -- flags : TInterface "Gtk" "CellRendererState"
    IO CInt


cellAreaActivateCell ::
    (MonadIO m, CellAreaK a, WidgetK b, CellRendererK c) =>
    a ->                                    -- _obj
    b ->                                    -- widget
    c ->                                    -- renderer
    Gdk.Event ->                            -- event
    Cairo.RectangleInt ->                   -- cell_area
    [CellRendererState] ->                  -- flags
    m Bool
cellAreaActivateCell _obj widget renderer event cell_area flags = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let widget' = unsafeManagedPtrCastPtr widget
    let renderer' = unsafeManagedPtrCastPtr renderer
    let event' = unsafeManagedPtrGetPtr event
    let cell_area' = unsafeManagedPtrGetPtr cell_area
    let flags' = gflagsToWord flags
    result <- gtk_cell_area_activate_cell _obj' widget' renderer' event' cell_area' flags'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr widget
    touchManagedPtr renderer
    touchManagedPtr event
    touchManagedPtr cell_area
    return result'

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

foreign import ccall "gtk_cell_area_add" gtk_cell_area_add :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    IO ()


cellAreaAdd ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    m ()
cellAreaAdd _obj renderer = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    gtk_cell_area_add _obj' renderer'
    touchManagedPtr _obj
    touchManagedPtr renderer
    return ()

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

foreign import ccall "gtk_cell_area_add_focus_sibling" gtk_cell_area_add_focus_sibling :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    Ptr CellRenderer ->                     -- sibling : TInterface "Gtk" "CellRenderer"
    IO ()


cellAreaAddFocusSibling ::
    (MonadIO m, CellAreaK a, CellRendererK b, CellRendererK c) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    c ->                                    -- sibling
    m ()
cellAreaAddFocusSibling _obj renderer sibling = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    let sibling' = unsafeManagedPtrCastPtr sibling
    gtk_cell_area_add_focus_sibling _obj' renderer' sibling'
    touchManagedPtr _obj
    touchManagedPtr renderer
    touchManagedPtr sibling
    return ()

-- method CellArea::apply_attributes
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tree_model", argType = TInterface "Gtk" "TreeModel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TreeIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_expander", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_expanded", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tree_model", argType = TInterface "Gtk" "TreeModel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "iter", argType = TInterface "Gtk" "TreeIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_expander", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_expanded", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_apply_attributes" gtk_cell_area_apply_attributes :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr TreeModel ->                        -- tree_model : TInterface "Gtk" "TreeModel"
    Ptr TreeIter ->                         -- iter : TInterface "Gtk" "TreeIter"
    CInt ->                                 -- is_expander : TBasicType TBoolean
    CInt ->                                 -- is_expanded : TBasicType TBoolean
    IO ()


cellAreaApplyAttributes ::
    (MonadIO m, CellAreaK a, TreeModelK b) =>
    a ->                                    -- _obj
    b ->                                    -- tree_model
    TreeIter ->                             -- iter
    Bool ->                                 -- is_expander
    Bool ->                                 -- is_expanded
    m ()
cellAreaApplyAttributes _obj tree_model iter is_expander is_expanded = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let tree_model' = unsafeManagedPtrCastPtr tree_model
    let iter' = unsafeManagedPtrGetPtr iter
    let is_expander' = (fromIntegral . fromEnum) is_expander
    let is_expanded' = (fromIntegral . fromEnum) is_expanded
    gtk_cell_area_apply_attributes _obj' tree_model' iter' is_expander' is_expanded'
    touchManagedPtr _obj
    touchManagedPtr tree_model
    touchManagedPtr iter
    return ()

-- method CellArea::attribute_connect
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attribute", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "column", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attribute", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "column", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_attribute_connect" gtk_cell_area_attribute_connect :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    CString ->                              -- attribute : TBasicType TUTF8
    Int32 ->                                -- column : TBasicType TInt32
    IO ()


cellAreaAttributeConnect ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    T.Text ->                               -- attribute
    Int32 ->                                -- column
    m ()
cellAreaAttributeConnect _obj renderer attribute column = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    attribute' <- textToCString attribute
    gtk_cell_area_attribute_connect _obj' renderer' attribute' column
    touchManagedPtr _obj
    touchManagedPtr renderer
    freeMem attribute'
    return ()

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

foreign import ccall "gtk_cell_area_attribute_disconnect" gtk_cell_area_attribute_disconnect :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    CString ->                              -- attribute : TBasicType TUTF8
    IO ()


cellAreaAttributeDisconnect ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    T.Text ->                               -- attribute
    m ()
cellAreaAttributeDisconnect _obj renderer attribute = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    attribute' <- textToCString attribute
    gtk_cell_area_attribute_disconnect _obj' renderer' attribute'
    touchManagedPtr _obj
    touchManagedPtr renderer
    freeMem attribute'
    return ()

-- method CellArea::attribute_get_column
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attribute", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attribute", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_attribute_get_column" gtk_cell_area_attribute_get_column :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    CString ->                              -- attribute : TBasicType TUTF8
    IO Int32


cellAreaAttributeGetColumn ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    T.Text ->                               -- attribute
    m Int32
cellAreaAttributeGetColumn _obj renderer attribute = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    attribute' <- textToCString attribute
    result <- gtk_cell_area_attribute_get_column _obj' renderer' attribute'
    touchManagedPtr _obj
    touchManagedPtr renderer
    freeMem attribute'
    return result

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

foreign import ccall "gtk_cell_area_cell_get_property" gtk_cell_area_cell_get_property :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    CString ->                              -- property_name : TBasicType TUTF8
    Ptr GValue ->                           -- value : TInterface "GObject" "Value"
    IO ()


cellAreaCellGetProperty ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    T.Text ->                               -- property_name
    GValue ->                               -- value
    m ()
cellAreaCellGetProperty _obj renderer property_name value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    property_name' <- textToCString property_name
    let value' = unsafeManagedPtrGetPtr value
    gtk_cell_area_cell_get_property _obj' renderer' property_name' value'
    touchManagedPtr _obj
    touchManagedPtr renderer
    touchManagedPtr value
    freeMem property_name'
    return ()

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

foreign import ccall "gtk_cell_area_cell_set_property" gtk_cell_area_cell_set_property :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    CString ->                              -- property_name : TBasicType TUTF8
    Ptr GValue ->                           -- value : TInterface "GObject" "Value"
    IO ()


cellAreaCellSetProperty ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    T.Text ->                               -- property_name
    GValue ->                               -- value
    m ()
cellAreaCellSetProperty _obj renderer property_name value = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    property_name' <- textToCString property_name
    let value' = unsafeManagedPtrGetPtr value
    gtk_cell_area_cell_set_property _obj' renderer' property_name' value'
    touchManagedPtr _obj
    touchManagedPtr renderer
    touchManagedPtr value
    freeMem property_name'
    return ()

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

foreign import ccall "gtk_cell_area_copy_context" gtk_cell_area_copy_context :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    IO (Ptr CellAreaContext)


cellAreaCopyContext ::
    (MonadIO m, CellAreaK a, CellAreaContextK b) =>
    a ->                                    -- _obj
    b ->                                    -- context
    m CellAreaContext
cellAreaCopyContext _obj context = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    result <- gtk_cell_area_copy_context _obj' context'
    checkUnexpectedReturnNULL "gtk_cell_area_copy_context" result
    result' <- (wrapObject CellAreaContext) result
    touchManagedPtr _obj
    touchManagedPtr context
    return result'

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

foreign import ccall "gtk_cell_area_create_context" gtk_cell_area_create_context :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    IO (Ptr CellAreaContext)


cellAreaCreateContext ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    m CellAreaContext
cellAreaCreateContext _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_cell_area_create_context _obj'
    checkUnexpectedReturnNULL "gtk_cell_area_create_context" result
    result' <- (wrapObject CellAreaContext) result
    touchManagedPtr _obj
    return result'

-- method CellArea::event
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "event", argType = TInterface "Gdk" "Event", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gtk" "CellRendererState", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "event", argType = TInterface "Gdk" "Event", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gtk" "CellRendererState", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_event" gtk_cell_area_event :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr Gdk.Event ->                        -- event : TInterface "Gdk" "Event"
    Ptr Cairo.RectangleInt ->               -- cell_area : TInterface "cairo" "RectangleInt"
    CUInt ->                                -- flags : TInterface "Gtk" "CellRendererState"
    IO Int32


cellAreaEvent ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    Gdk.Event ->                            -- event
    Cairo.RectangleInt ->                   -- cell_area
    [CellRendererState] ->                  -- flags
    m Int32
cellAreaEvent _obj context widget event cell_area flags = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    let event' = unsafeManagedPtrGetPtr event
    let cell_area' = unsafeManagedPtrGetPtr cell_area
    let flags' = gflagsToWord flags
    result <- gtk_cell_area_event _obj' context' widget' event' cell_area' flags'
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    touchManagedPtr event
    touchManagedPtr cell_area
    return result

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

foreign import ccall "gtk_cell_area_focus" gtk_cell_area_focus :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    CUInt ->                                -- direction : TInterface "Gtk" "DirectionType"
    IO CInt


cellAreaFocus ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    DirectionType ->                        -- direction
    m Bool
cellAreaFocus _obj direction = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let direction' = (fromIntegral . fromEnum) direction
    result <- gtk_cell_area_focus _obj' direction'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_cell_area_foreach" gtk_cell_area_foreach :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    FunPtr CellCallbackC ->                 -- callback : TInterface "Gtk" "CellCallback"
    Ptr () ->                               -- callback_data : TBasicType TVoid
    IO ()


cellAreaForeach ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    CellCallback ->                         -- callback
    m ()
cellAreaForeach _obj callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    callback' <- mkCellCallback (cellCallbackWrapper Nothing callback)
    let callback_data = nullPtr
    gtk_cell_area_foreach _obj' callback' callback_data
    safeFreeFunPtr $ castFunPtrToPtr callback'
    touchManagedPtr _obj
    return ()

-- method CellArea::foreach_alloc
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "background_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gtk" "CellAllocCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeCall, argClosure = 6, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "background_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "callback", argType = TInterface "Gtk" "CellAllocCallback", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeCall, argClosure = 6, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_foreach_alloc" gtk_cell_area_foreach_alloc :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr Cairo.RectangleInt ->               -- cell_area : TInterface "cairo" "RectangleInt"
    Ptr Cairo.RectangleInt ->               -- background_area : TInterface "cairo" "RectangleInt"
    FunPtr CellAllocCallbackC ->            -- callback : TInterface "Gtk" "CellAllocCallback"
    Ptr () ->                               -- callback_data : TBasicType TVoid
    IO ()


cellAreaForeachAlloc ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    Cairo.RectangleInt ->                   -- cell_area
    Cairo.RectangleInt ->                   -- background_area
    CellAllocCallback ->                    -- callback
    m ()
cellAreaForeachAlloc _obj context widget cell_area background_area callback = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    let cell_area' = unsafeManagedPtrGetPtr cell_area
    let background_area' = unsafeManagedPtrGetPtr background_area
    callback' <- mkCellAllocCallback (cellAllocCallbackWrapper Nothing callback)
    let callback_data = nullPtr
    gtk_cell_area_foreach_alloc _obj' context' widget' cell_area' background_area' callback' callback_data
    safeFreeFunPtr $ castFunPtrToPtr callback'
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    touchManagedPtr cell_area
    touchManagedPtr background_area
    return ()

-- method CellArea::get_cell_allocation
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "allocation", argType = TInterface "cairo" "RectangleInt", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_get_cell_allocation" gtk_cell_area_get_cell_allocation :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    Ptr Cairo.RectangleInt ->               -- cell_area : TInterface "cairo" "RectangleInt"
    Ptr Cairo.RectangleInt ->               -- allocation : TInterface "cairo" "RectangleInt"
    IO ()


cellAreaGetCellAllocation ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c, CellRendererK d) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    d ->                                    -- renderer
    Cairo.RectangleInt ->                   -- cell_area
    m (Cairo.RectangleInt)
cellAreaGetCellAllocation _obj context widget renderer cell_area = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    let renderer' = unsafeManagedPtrCastPtr renderer
    let cell_area' = unsafeManagedPtrGetPtr cell_area
    allocation <- callocBoxedBytes 16 :: IO (Ptr Cairo.RectangleInt)
    gtk_cell_area_get_cell_allocation _obj' context' widget' renderer' cell_area' allocation
    allocation' <- (wrapBoxed Cairo.RectangleInt) allocation
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    touchManagedPtr renderer
    touchManagedPtr cell_area
    return allocation'

-- method CellArea::get_cell_at_position
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "alloc_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "CellRenderer"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_get_cell_at_position" gtk_cell_area_get_cell_at_position :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr Cairo.RectangleInt ->               -- cell_area : TInterface "cairo" "RectangleInt"
    Int32 ->                                -- x : TBasicType TInt32
    Int32 ->                                -- y : TBasicType TInt32
    Ptr Cairo.RectangleInt ->               -- alloc_area : TInterface "cairo" "RectangleInt"
    IO (Ptr CellRenderer)


cellAreaGetCellAtPosition ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    Cairo.RectangleInt ->                   -- cell_area
    Int32 ->                                -- x
    Int32 ->                                -- y
    m (CellRenderer,Cairo.RectangleInt)
cellAreaGetCellAtPosition _obj context widget cell_area x y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    let cell_area' = unsafeManagedPtrGetPtr cell_area
    alloc_area <- callocBoxedBytes 16 :: IO (Ptr Cairo.RectangleInt)
    result <- gtk_cell_area_get_cell_at_position _obj' context' widget' cell_area' x y alloc_area
    checkUnexpectedReturnNULL "gtk_cell_area_get_cell_at_position" result
    result' <- (newObject CellRenderer) result
    alloc_area' <- (wrapBoxed Cairo.RectangleInt) alloc_area
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    touchManagedPtr cell_area
    return (result', alloc_area')

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

foreign import ccall "gtk_cell_area_get_current_path_string" gtk_cell_area_get_current_path_string :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    IO CString


cellAreaGetCurrentPathString ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    m T.Text
cellAreaGetCurrentPathString _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_cell_area_get_current_path_string _obj'
    checkUnexpectedReturnNULL "gtk_cell_area_get_current_path_string" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_cell_area_get_edit_widget" gtk_cell_area_get_edit_widget :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    IO (Ptr CellEditable)


cellAreaGetEditWidget ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    m CellEditable
cellAreaGetEditWidget _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_cell_area_get_edit_widget _obj'
    checkUnexpectedReturnNULL "gtk_cell_area_get_edit_widget" result
    result' <- (newObject CellEditable) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_cell_area_get_edited_cell" gtk_cell_area_get_edited_cell :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    IO (Ptr CellRenderer)


cellAreaGetEditedCell ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    m CellRenderer
cellAreaGetEditedCell _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_cell_area_get_edited_cell _obj'
    checkUnexpectedReturnNULL "gtk_cell_area_get_edited_cell" result
    result' <- (newObject CellRenderer) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_cell_area_get_focus_cell" gtk_cell_area_get_focus_cell :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    IO (Ptr CellRenderer)


cellAreaGetFocusCell ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    m CellRenderer
cellAreaGetFocusCell _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_cell_area_get_focus_cell _obj'
    checkUnexpectedReturnNULL "gtk_cell_area_get_focus_cell" result
    result' <- (newObject CellRenderer) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_cell_area_get_focus_from_sibling" gtk_cell_area_get_focus_from_sibling :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    IO (Ptr CellRenderer)


cellAreaGetFocusFromSibling ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    m CellRenderer
cellAreaGetFocusFromSibling _obj renderer = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    result <- gtk_cell_area_get_focus_from_sibling _obj' renderer'
    checkUnexpectedReturnNULL "gtk_cell_area_get_focus_from_sibling" result
    result' <- (newObject CellRenderer) result
    touchManagedPtr _obj
    touchManagedPtr renderer
    return result'

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

foreign import ccall "gtk_cell_area_get_focus_siblings" gtk_cell_area_get_focus_siblings :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    IO (Ptr (GList (Ptr CellRenderer)))


cellAreaGetFocusSiblings ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    m [CellRenderer]
cellAreaGetFocusSiblings _obj renderer = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    result <- gtk_cell_area_get_focus_siblings _obj' renderer'
    checkUnexpectedReturnNULL "gtk_cell_area_get_focus_siblings" result
    result' <- unpackGList result
    result'' <- mapM (newObject CellRenderer) result'
    touchManagedPtr _obj
    touchManagedPtr renderer
    return result''

-- method CellArea::get_preferred_height
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "minimum_height", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "natural_height", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_get_preferred_height" gtk_cell_area_get_preferred_height :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr Int32 ->                            -- minimum_height : TBasicType TInt32
    Ptr Int32 ->                            -- natural_height : TBasicType TInt32
    IO ()


cellAreaGetPreferredHeight ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    m (Int32,Int32)
cellAreaGetPreferredHeight _obj context widget = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    minimum_height <- allocMem :: IO (Ptr Int32)
    natural_height <- allocMem :: IO (Ptr Int32)
    gtk_cell_area_get_preferred_height _obj' context' widget' minimum_height natural_height
    minimum_height' <- peek minimum_height
    natural_height' <- peek natural_height
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    freeMem minimum_height
    freeMem natural_height
    return (minimum_height', natural_height')

-- method CellArea::get_preferred_height_for_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "width", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "minimum_height", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "natural_height", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "width", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_get_preferred_height_for_width" gtk_cell_area_get_preferred_height_for_width :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Int32 ->                                -- width : TBasicType TInt32
    Ptr Int32 ->                            -- minimum_height : TBasicType TInt32
    Ptr Int32 ->                            -- natural_height : TBasicType TInt32
    IO ()


cellAreaGetPreferredHeightForWidth ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    Int32 ->                                -- width
    m (Int32,Int32)
cellAreaGetPreferredHeightForWidth _obj context widget width = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    minimum_height <- allocMem :: IO (Ptr Int32)
    natural_height <- allocMem :: IO (Ptr Int32)
    gtk_cell_area_get_preferred_height_for_width _obj' context' widget' width minimum_height natural_height
    minimum_height' <- peek minimum_height
    natural_height' <- peek natural_height
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    freeMem minimum_height
    freeMem natural_height
    return (minimum_height', natural_height')

-- method CellArea::get_preferred_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "minimum_width", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "natural_width", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_get_preferred_width" gtk_cell_area_get_preferred_width :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr Int32 ->                            -- minimum_width : TBasicType TInt32
    Ptr Int32 ->                            -- natural_width : TBasicType TInt32
    IO ()


cellAreaGetPreferredWidth ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    m (Int32,Int32)
cellAreaGetPreferredWidth _obj context widget = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    minimum_width <- allocMem :: IO (Ptr Int32)
    natural_width <- allocMem :: IO (Ptr Int32)
    gtk_cell_area_get_preferred_width _obj' context' widget' minimum_width natural_width
    minimum_width' <- peek minimum_width
    natural_width' <- peek natural_width
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    freeMem minimum_width
    freeMem natural_width
    return (minimum_width', natural_width')

-- method CellArea::get_preferred_width_for_height
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "height", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "minimum_width", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "natural_width", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "height", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_get_preferred_width_for_height" gtk_cell_area_get_preferred_width_for_height :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Int32 ->                                -- height : TBasicType TInt32
    Ptr Int32 ->                            -- minimum_width : TBasicType TInt32
    Ptr Int32 ->                            -- natural_width : TBasicType TInt32
    IO ()


cellAreaGetPreferredWidthForHeight ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    Int32 ->                                -- height
    m (Int32,Int32)
cellAreaGetPreferredWidthForHeight _obj context widget height = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    minimum_width <- allocMem :: IO (Ptr Int32)
    natural_width <- allocMem :: IO (Ptr Int32)
    gtk_cell_area_get_preferred_width_for_height _obj' context' widget' height minimum_width natural_width
    minimum_width' <- peek minimum_width
    natural_width' <- peek natural_width
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    freeMem minimum_width
    freeMem natural_width
    return (minimum_width', natural_width')

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

foreign import ccall "gtk_cell_area_get_request_mode" gtk_cell_area_get_request_mode :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    IO CUInt


cellAreaGetRequestMode ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    m SizeRequestMode
cellAreaGetRequestMode _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_cell_area_get_request_mode _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_cell_area_has_renderer" gtk_cell_area_has_renderer :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    IO CInt


cellAreaHasRenderer ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    m Bool
cellAreaHasRenderer _obj renderer = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    result <- gtk_cell_area_has_renderer _obj' renderer'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr renderer
    return result'

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

foreign import ccall "gtk_cell_area_inner_cell_area" gtk_cell_area_inner_cell_area :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr Cairo.RectangleInt ->               -- cell_area : TInterface "cairo" "RectangleInt"
    Ptr Cairo.RectangleInt ->               -- inner_area : TInterface "cairo" "RectangleInt"
    IO ()


cellAreaInnerCellArea ::
    (MonadIO m, CellAreaK a, WidgetK b) =>
    a ->                                    -- _obj
    b ->                                    -- widget
    Cairo.RectangleInt ->                   -- cell_area
    m (Cairo.RectangleInt)
cellAreaInnerCellArea _obj widget cell_area = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let widget' = unsafeManagedPtrCastPtr widget
    let cell_area' = unsafeManagedPtrGetPtr cell_area
    inner_area <- callocBoxedBytes 16 :: IO (Ptr Cairo.RectangleInt)
    gtk_cell_area_inner_cell_area _obj' widget' cell_area' inner_area
    inner_area' <- (wrapBoxed Cairo.RectangleInt) inner_area
    touchManagedPtr _obj
    touchManagedPtr widget
    touchManagedPtr cell_area
    return inner_area'

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

foreign import ccall "gtk_cell_area_is_activatable" gtk_cell_area_is_activatable :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    IO CInt


cellAreaIsActivatable ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    m Bool
cellAreaIsActivatable _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_cell_area_is_activatable _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_cell_area_is_focus_sibling" gtk_cell_area_is_focus_sibling :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    Ptr CellRenderer ->                     -- sibling : TInterface "Gtk" "CellRenderer"
    IO CInt


cellAreaIsFocusSibling ::
    (MonadIO m, CellAreaK a, CellRendererK b, CellRendererK c) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    c ->                                    -- sibling
    m Bool
cellAreaIsFocusSibling _obj renderer sibling = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    let sibling' = unsafeManagedPtrCastPtr sibling
    result <- gtk_cell_area_is_focus_sibling _obj' renderer' sibling'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr renderer
    touchManagedPtr sibling
    return result'

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

foreign import ccall "gtk_cell_area_remove" gtk_cell_area_remove :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    IO ()


cellAreaRemove ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    m ()
cellAreaRemove _obj renderer = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    gtk_cell_area_remove _obj' renderer'
    touchManagedPtr _obj
    touchManagedPtr renderer
    return ()

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

foreign import ccall "gtk_cell_area_remove_focus_sibling" gtk_cell_area_remove_focus_sibling :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    Ptr CellRenderer ->                     -- sibling : TInterface "Gtk" "CellRenderer"
    IO ()


cellAreaRemoveFocusSibling ::
    (MonadIO m, CellAreaK a, CellRendererK b, CellRendererK c) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    c ->                                    -- sibling
    m ()
cellAreaRemoveFocusSibling _obj renderer sibling = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    let sibling' = unsafeManagedPtrCastPtr sibling
    gtk_cell_area_remove_focus_sibling _obj' renderer' sibling'
    touchManagedPtr _obj
    touchManagedPtr renderer
    touchManagedPtr sibling
    return ()

-- method CellArea::render
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cr", argType = TInterface "cairo" "Context", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "background_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gtk" "CellRendererState", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "paint_focus", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TInterface "Gtk" "CellAreaContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cr", argType = TInterface "cairo" "Context", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "background_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell_area", argType = TInterface "cairo" "RectangleInt", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "Gtk" "CellRendererState", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "paint_focus", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_render" gtk_cell_area_render :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellAreaContext ->                  -- context : TInterface "Gtk" "CellAreaContext"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Ptr Cairo.Context ->                    -- cr : TInterface "cairo" "Context"
    Ptr Cairo.RectangleInt ->               -- background_area : TInterface "cairo" "RectangleInt"
    Ptr Cairo.RectangleInt ->               -- cell_area : TInterface "cairo" "RectangleInt"
    CUInt ->                                -- flags : TInterface "Gtk" "CellRendererState"
    CInt ->                                 -- paint_focus : TBasicType TBoolean
    IO ()


cellAreaRender ::
    (MonadIO m, CellAreaK a, CellAreaContextK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- context
    c ->                                    -- widget
    Cairo.Context ->                        -- cr
    Cairo.RectangleInt ->                   -- background_area
    Cairo.RectangleInt ->                   -- cell_area
    [CellRendererState] ->                  -- flags
    Bool ->                                 -- paint_focus
    m ()
cellAreaRender _obj context widget cr background_area cell_area flags paint_focus = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let context' = unsafeManagedPtrCastPtr context
    let widget' = unsafeManagedPtrCastPtr widget
    let cr' = unsafeManagedPtrGetPtr cr
    let background_area' = unsafeManagedPtrGetPtr background_area
    let cell_area' = unsafeManagedPtrGetPtr cell_area
    let flags' = gflagsToWord flags
    let paint_focus' = (fromIntegral . fromEnum) paint_focus
    gtk_cell_area_render _obj' context' widget' cr' background_area' cell_area' flags' paint_focus'
    touchManagedPtr _obj
    touchManagedPtr context
    touchManagedPtr widget
    touchManagedPtr cr
    touchManagedPtr background_area
    touchManagedPtr cell_area
    return ()

-- method CellArea::request_renderer
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "orientation", argType = TInterface "Gtk" "Orientation", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "for_size", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "minimum_size", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "natural_size", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "CellArea", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "renderer", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "orientation", argType = TInterface "Gtk" "Orientation", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "for_size", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_cell_area_request_renderer" gtk_cell_area_request_renderer :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    CUInt ->                                -- orientation : TInterface "Gtk" "Orientation"
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    Int32 ->                                -- for_size : TBasicType TInt32
    Ptr Int32 ->                            -- minimum_size : TBasicType TInt32
    Ptr Int32 ->                            -- natural_size : TBasicType TInt32
    IO ()


cellAreaRequestRenderer ::
    (MonadIO m, CellAreaK a, CellRendererK b, WidgetK c) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    Orientation ->                          -- orientation
    c ->                                    -- widget
    Int32 ->                                -- for_size
    m (Int32,Int32)
cellAreaRequestRenderer _obj renderer orientation widget for_size = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    let orientation' = (fromIntegral . fromEnum) orientation
    let widget' = unsafeManagedPtrCastPtr widget
    minimum_size <- allocMem :: IO (Ptr Int32)
    natural_size <- allocMem :: IO (Ptr Int32)
    gtk_cell_area_request_renderer _obj' renderer' orientation' widget' for_size minimum_size natural_size
    minimum_size' <- peek minimum_size
    natural_size' <- peek natural_size
    touchManagedPtr _obj
    touchManagedPtr renderer
    touchManagedPtr widget
    freeMem minimum_size
    freeMem natural_size
    return (minimum_size', natural_size')

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

foreign import ccall "gtk_cell_area_set_focus_cell" gtk_cell_area_set_focus_cell :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    Ptr CellRenderer ->                     -- renderer : TInterface "Gtk" "CellRenderer"
    IO ()


cellAreaSetFocusCell ::
    (MonadIO m, CellAreaK a, CellRendererK b) =>
    a ->                                    -- _obj
    b ->                                    -- renderer
    m ()
cellAreaSetFocusCell _obj renderer = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let renderer' = unsafeManagedPtrCastPtr renderer
    gtk_cell_area_set_focus_cell _obj' renderer'
    touchManagedPtr _obj
    touchManagedPtr renderer
    return ()

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

foreign import ccall "gtk_cell_area_stop_editing" gtk_cell_area_stop_editing :: 
    Ptr CellArea ->                         -- _obj : TInterface "Gtk" "CellArea"
    CInt ->                                 -- canceled : TBasicType TBoolean
    IO ()


cellAreaStopEditing ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- canceled
    m ()
cellAreaStopEditing _obj canceled = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let canceled' = (fromIntegral . fromEnum) canceled
    gtk_cell_area_stop_editing _obj' canceled'
    touchManagedPtr _obj
    return ()