{- |
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.IconView
    ( 

-- * Exported types
    IconView(..)                            ,
    IconViewK                               ,
    toIconView                              ,
    noIconView                              ,


 -- * Methods
-- ** iconViewConvertWidgetToBinWindowCoords
    iconViewConvertWidgetToBinWindowCoords  ,


-- ** iconViewCreateDragIcon
    iconViewCreateDragIcon                  ,


-- ** iconViewEnableModelDragDest
    iconViewEnableModelDragDest             ,


-- ** iconViewEnableModelDragSource
    iconViewEnableModelDragSource           ,


-- ** iconViewGetActivateOnSingleClick
    iconViewGetActivateOnSingleClick        ,


-- ** iconViewGetCellRect
    iconViewGetCellRect                     ,


-- ** iconViewGetColumnSpacing
    iconViewGetColumnSpacing                ,


-- ** iconViewGetColumns
    iconViewGetColumns                      ,


-- ** iconViewGetCursor
    iconViewGetCursor                       ,


-- ** iconViewGetDestItemAtPos
    iconViewGetDestItemAtPos                ,


-- ** iconViewGetDragDestItem
    iconViewGetDragDestItem                 ,


-- ** iconViewGetItemAtPos
    iconViewGetItemAtPos                    ,


-- ** iconViewGetItemColumn
    iconViewGetItemColumn                   ,


-- ** iconViewGetItemOrientation
    iconViewGetItemOrientation              ,


-- ** iconViewGetItemPadding
    iconViewGetItemPadding                  ,


-- ** iconViewGetItemRow
    iconViewGetItemRow                      ,


-- ** iconViewGetItemWidth
    iconViewGetItemWidth                    ,


-- ** iconViewGetMargin
    iconViewGetMargin                       ,


-- ** iconViewGetMarkupColumn
    iconViewGetMarkupColumn                 ,


-- ** iconViewGetModel
    iconViewGetModel                        ,


-- ** iconViewGetPathAtPos
    iconViewGetPathAtPos                    ,


-- ** iconViewGetPixbufColumn
    iconViewGetPixbufColumn                 ,


-- ** iconViewGetReorderable
    iconViewGetReorderable                  ,


-- ** iconViewGetRowSpacing
    iconViewGetRowSpacing                   ,


-- ** iconViewGetSelectedItems
    iconViewGetSelectedItems                ,


-- ** iconViewGetSelectionMode
    iconViewGetSelectionMode                ,


-- ** iconViewGetSpacing
    iconViewGetSpacing                      ,


-- ** iconViewGetTextColumn
    iconViewGetTextColumn                   ,


-- ** iconViewGetTooltipColumn
    iconViewGetTooltipColumn                ,


-- ** iconViewGetTooltipContext
    iconViewGetTooltipContext               ,


-- ** iconViewGetVisibleRange
    iconViewGetVisibleRange                 ,


-- ** iconViewItemActivated
    iconViewItemActivated                   ,


-- ** iconViewNew
    iconViewNew                             ,


-- ** iconViewNewWithArea
    iconViewNewWithArea                     ,


-- ** iconViewNewWithModel
    iconViewNewWithModel                    ,


-- ** iconViewPathIsSelected
    iconViewPathIsSelected                  ,


-- ** iconViewScrollToPath
    iconViewScrollToPath                    ,


-- ** iconViewSelectAll
    iconViewSelectAll                       ,


-- ** iconViewSelectPath
    iconViewSelectPath                      ,


-- ** iconViewSelectedForeach
    iconViewSelectedForeach                 ,


-- ** iconViewSetActivateOnSingleClick
    iconViewSetActivateOnSingleClick        ,


-- ** iconViewSetColumnSpacing
    iconViewSetColumnSpacing                ,


-- ** iconViewSetColumns
    iconViewSetColumns                      ,


-- ** iconViewSetCursor
    iconViewSetCursor                       ,


-- ** iconViewSetDragDestItem
    iconViewSetDragDestItem                 ,


-- ** iconViewSetItemOrientation
    iconViewSetItemOrientation              ,


-- ** iconViewSetItemPadding
    iconViewSetItemPadding                  ,


-- ** iconViewSetItemWidth
    iconViewSetItemWidth                    ,


-- ** iconViewSetMargin
    iconViewSetMargin                       ,


-- ** iconViewSetMarkupColumn
    iconViewSetMarkupColumn                 ,


-- ** iconViewSetModel
    iconViewSetModel                        ,


-- ** iconViewSetPixbufColumn
    iconViewSetPixbufColumn                 ,


-- ** iconViewSetReorderable
    iconViewSetReorderable                  ,


-- ** iconViewSetRowSpacing
    iconViewSetRowSpacing                   ,


-- ** iconViewSetSelectionMode
    iconViewSetSelectionMode                ,


-- ** iconViewSetSpacing
    iconViewSetSpacing                      ,


-- ** iconViewSetTextColumn
    iconViewSetTextColumn                   ,


-- ** iconViewSetTooltipCell
    iconViewSetTooltipCell                  ,


-- ** iconViewSetTooltipColumn
    iconViewSetTooltipColumn                ,


-- ** iconViewSetTooltipItem
    iconViewSetTooltipItem                  ,


-- ** iconViewUnselectAll
    iconViewUnselectAll                     ,


-- ** iconViewUnselectPath
    iconViewUnselectPath                    ,


-- ** iconViewUnsetModelDragDest
    iconViewUnsetModelDragDest              ,


-- ** iconViewUnsetModelDragSource
    iconViewUnsetModelDragSource            ,




 -- * Properties
-- ** ActivateOnSingleClick
    IconViewActivateOnSingleClickPropertyInfo,
    constructIconViewActivateOnSingleClick  ,
    getIconViewActivateOnSingleClick        ,
    setIconViewActivateOnSingleClick        ,


-- ** CellArea
    IconViewCellAreaPropertyInfo            ,
    constructIconViewCellArea               ,
    getIconViewCellArea                     ,


-- ** ColumnSpacing
    IconViewColumnSpacingPropertyInfo       ,
    constructIconViewColumnSpacing          ,
    getIconViewColumnSpacing                ,
    setIconViewColumnSpacing                ,


-- ** Columns
    IconViewColumnsPropertyInfo             ,
    constructIconViewColumns                ,
    getIconViewColumns                      ,
    setIconViewColumns                      ,


-- ** ItemOrientation
    IconViewItemOrientationPropertyInfo     ,
    constructIconViewItemOrientation        ,
    getIconViewItemOrientation              ,
    setIconViewItemOrientation              ,


-- ** ItemPadding
    IconViewItemPaddingPropertyInfo         ,
    constructIconViewItemPadding            ,
    getIconViewItemPadding                  ,
    setIconViewItemPadding                  ,


-- ** ItemWidth
    IconViewItemWidthPropertyInfo           ,
    constructIconViewItemWidth              ,
    getIconViewItemWidth                    ,
    setIconViewItemWidth                    ,


-- ** Margin
    IconViewMarginPropertyInfo              ,
    constructIconViewMargin                 ,
    getIconViewMargin                       ,
    setIconViewMargin                       ,


-- ** MarkupColumn
    IconViewMarkupColumnPropertyInfo        ,
    constructIconViewMarkupColumn           ,
    getIconViewMarkupColumn                 ,
    setIconViewMarkupColumn                 ,


-- ** Model
    IconViewModelPropertyInfo               ,
    constructIconViewModel                  ,
    getIconViewModel                        ,
    setIconViewModel                        ,


-- ** PixbufColumn
    IconViewPixbufColumnPropertyInfo        ,
    constructIconViewPixbufColumn           ,
    getIconViewPixbufColumn                 ,
    setIconViewPixbufColumn                 ,


-- ** Reorderable
    IconViewReorderablePropertyInfo         ,
    constructIconViewReorderable            ,
    getIconViewReorderable                  ,
    setIconViewReorderable                  ,


-- ** RowSpacing
    IconViewRowSpacingPropertyInfo          ,
    constructIconViewRowSpacing             ,
    getIconViewRowSpacing                   ,
    setIconViewRowSpacing                   ,


-- ** SelectionMode
    IconViewSelectionModePropertyInfo       ,
    constructIconViewSelectionMode          ,
    getIconViewSelectionMode                ,
    setIconViewSelectionMode                ,


-- ** Spacing
    IconViewSpacingPropertyInfo             ,
    constructIconViewSpacing                ,
    getIconViewSpacing                      ,
    setIconViewSpacing                      ,


-- ** TextColumn
    IconViewTextColumnPropertyInfo          ,
    constructIconViewTextColumn             ,
    getIconViewTextColumn                   ,
    setIconViewTextColumn                   ,


-- ** TooltipColumn
    IconViewTooltipColumnPropertyInfo       ,
    constructIconViewTooltipColumn          ,
    getIconViewTooltipColumn                ,
    setIconViewTooltipColumn                ,




 -- * Signals
-- ** ActivateCursorItem
    IconViewActivateCursorItemCallback      ,
    IconViewActivateCursorItemCallbackC     ,
    IconViewActivateCursorItemSignalInfo    ,
    afterIconViewActivateCursorItem         ,
    iconViewActivateCursorItemCallbackWrapper,
    iconViewActivateCursorItemClosure       ,
    mkIconViewActivateCursorItemCallback    ,
    noIconViewActivateCursorItemCallback    ,
    onIconViewActivateCursorItem            ,


-- ** ItemActivated
    IconViewItemActivatedCallback           ,
    IconViewItemActivatedCallbackC          ,
    IconViewItemActivatedSignalInfo         ,
    afterIconViewItemActivated              ,
    iconViewItemActivatedCallbackWrapper    ,
    iconViewItemActivatedClosure            ,
    mkIconViewItemActivatedCallback         ,
    noIconViewItemActivatedCallback         ,
    onIconViewItemActivated                 ,


-- ** MoveCursor
    IconViewMoveCursorCallback              ,
    IconViewMoveCursorCallbackC             ,
    IconViewMoveCursorSignalInfo            ,
    afterIconViewMoveCursor                 ,
    iconViewMoveCursorCallbackWrapper       ,
    iconViewMoveCursorClosure               ,
    mkIconViewMoveCursorCallback            ,
    noIconViewMoveCursorCallback            ,
    onIconViewMoveCursor                    ,


-- ** SelectAll
    IconViewSelectAllCallback               ,
    IconViewSelectAllCallbackC              ,
    IconViewSelectAllSignalInfo             ,
    afterIconViewSelectAll                  ,
    iconViewSelectAllCallbackWrapper        ,
    iconViewSelectAllClosure                ,
    mkIconViewSelectAllCallback             ,
    noIconViewSelectAllCallback             ,
    onIconViewSelectAll                     ,


-- ** SelectCursorItem
    IconViewSelectCursorItemCallback        ,
    IconViewSelectCursorItemCallbackC       ,
    IconViewSelectCursorItemSignalInfo      ,
    afterIconViewSelectCursorItem           ,
    iconViewSelectCursorItemCallbackWrapper ,
    iconViewSelectCursorItemClosure         ,
    mkIconViewSelectCursorItemCallback      ,
    noIconViewSelectCursorItemCallback      ,
    onIconViewSelectCursorItem              ,


-- ** SelectionChanged
    IconViewSelectionChangedCallback        ,
    IconViewSelectionChangedCallbackC       ,
    IconViewSelectionChangedSignalInfo      ,
    afterIconViewSelectionChanged           ,
    iconViewSelectionChangedCallbackWrapper ,
    iconViewSelectionChangedClosure         ,
    mkIconViewSelectionChangedCallback      ,
    noIconViewSelectionChangedCallback      ,
    onIconViewSelectionChanged              ,


-- ** ToggleCursorItem
    IconViewToggleCursorItemCallback        ,
    IconViewToggleCursorItemCallbackC       ,
    IconViewToggleCursorItemSignalInfo      ,
    afterIconViewToggleCursorItem           ,
    iconViewToggleCursorItemCallbackWrapper ,
    iconViewToggleCursorItemClosure         ,
    mkIconViewToggleCursorItemCallback      ,
    noIconViewToggleCursorItemCallback      ,
    onIconViewToggleCursorItem              ,


-- ** UnselectAll
    IconViewUnselectAllCallback             ,
    IconViewUnselectAllCallbackC            ,
    IconViewUnselectAllSignalInfo           ,
    afterIconViewUnselectAll                ,
    iconViewUnselectAllCallbackWrapper      ,
    iconViewUnselectAllClosure              ,
    mkIconViewUnselectAllCallback           ,
    noIconViewUnselectAllCallback           ,
    onIconViewUnselectAll                   ,




    ) 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.Atk as Atk
import qualified GI.GObject as GObject
import qualified GI.Gdk as Gdk
import qualified GI.Cairo as Cairo

newtype IconView = IconView (ForeignPtr IconView)
foreign import ccall "gtk_icon_view_get_type"
    c_gtk_icon_view_get_type :: IO GType

type instance ParentTypes IconView = IconViewParentTypes
type IconViewParentTypes = '[Container, Widget, GObject.Object, Atk.ImplementorIface, Buildable, CellLayout, Scrollable]

instance GObject IconView where
    gobjectIsInitiallyUnowned _ = True
    gobjectType _ = c_gtk_icon_view_get_type
    

class GObject o => IconViewK o
instance (GObject o, IsDescendantOf IconView o) => IconViewK o

toIconView :: IconViewK o => o -> IO IconView
toIconView = unsafeCastTo IconView

noIconView :: Maybe IconView
noIconView = Nothing

-- signal IconView::activate-cursor-item
type IconViewActivateCursorItemCallback =
    IO Bool

noIconViewActivateCursorItemCallback :: Maybe IconViewActivateCursorItemCallback
noIconViewActivateCursorItemCallback = Nothing

type IconViewActivateCursorItemCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO CInt

foreign import ccall "wrapper"
    mkIconViewActivateCursorItemCallback :: IconViewActivateCursorItemCallbackC -> IO (FunPtr IconViewActivateCursorItemCallbackC)

iconViewActivateCursorItemClosure :: IconViewActivateCursorItemCallback -> IO Closure
iconViewActivateCursorItemClosure cb = newCClosure =<< mkIconViewActivateCursorItemCallback wrapped
    where wrapped = iconViewActivateCursorItemCallbackWrapper cb

iconViewActivateCursorItemCallbackWrapper ::
    IconViewActivateCursorItemCallback ->
    Ptr () ->
    Ptr () ->
    IO CInt
iconViewActivateCursorItemCallbackWrapper _cb _ _ = do
    result <- _cb 
    let result' = (fromIntegral . fromEnum) result
    return result'

onIconViewActivateCursorItem :: (GObject a, MonadIO m) => a -> IconViewActivateCursorItemCallback -> m SignalHandlerId
onIconViewActivateCursorItem obj cb = liftIO $ connectIconViewActivateCursorItem obj cb SignalConnectBefore
afterIconViewActivateCursorItem :: (GObject a, MonadIO m) => a -> IconViewActivateCursorItemCallback -> m SignalHandlerId
afterIconViewActivateCursorItem obj cb = connectIconViewActivateCursorItem obj cb SignalConnectAfter

connectIconViewActivateCursorItem :: (GObject a, MonadIO m) =>
                                     a -> IconViewActivateCursorItemCallback -> SignalConnectMode -> m SignalHandlerId
connectIconViewActivateCursorItem obj cb after = liftIO $ do
    cb' <- mkIconViewActivateCursorItemCallback (iconViewActivateCursorItemCallbackWrapper cb)
    connectSignalFunPtr obj "activate-cursor-item" cb' after

-- signal IconView::item-activated
type IconViewItemActivatedCallback =
    TreePath ->
    IO ()

noIconViewItemActivatedCallback :: Maybe IconViewItemActivatedCallback
noIconViewItemActivatedCallback = Nothing

type IconViewItemActivatedCallbackC =
    Ptr () ->                               -- object
    Ptr TreePath ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkIconViewItemActivatedCallback :: IconViewItemActivatedCallbackC -> IO (FunPtr IconViewItemActivatedCallbackC)

iconViewItemActivatedClosure :: IconViewItemActivatedCallback -> IO Closure
iconViewItemActivatedClosure cb = newCClosure =<< mkIconViewItemActivatedCallback wrapped
    where wrapped = iconViewItemActivatedCallbackWrapper cb

iconViewItemActivatedCallbackWrapper ::
    IconViewItemActivatedCallback ->
    Ptr () ->
    Ptr TreePath ->
    Ptr () ->
    IO ()
iconViewItemActivatedCallbackWrapper _cb _ path _ = do
    path' <- (newBoxed TreePath) path
    _cb  path'

onIconViewItemActivated :: (GObject a, MonadIO m) => a -> IconViewItemActivatedCallback -> m SignalHandlerId
onIconViewItemActivated obj cb = liftIO $ connectIconViewItemActivated obj cb SignalConnectBefore
afterIconViewItemActivated :: (GObject a, MonadIO m) => a -> IconViewItemActivatedCallback -> m SignalHandlerId
afterIconViewItemActivated obj cb = connectIconViewItemActivated obj cb SignalConnectAfter

connectIconViewItemActivated :: (GObject a, MonadIO m) =>
                                a -> IconViewItemActivatedCallback -> SignalConnectMode -> m SignalHandlerId
connectIconViewItemActivated obj cb after = liftIO $ do
    cb' <- mkIconViewItemActivatedCallback (iconViewItemActivatedCallbackWrapper cb)
    connectSignalFunPtr obj "item-activated" cb' after

-- signal IconView::move-cursor
type IconViewMoveCursorCallback =
    MovementStep ->
    Int32 ->
    IO Bool

noIconViewMoveCursorCallback :: Maybe IconViewMoveCursorCallback
noIconViewMoveCursorCallback = Nothing

type IconViewMoveCursorCallbackC =
    Ptr () ->                               -- object
    CUInt ->
    Int32 ->
    Ptr () ->                               -- user_data
    IO CInt

foreign import ccall "wrapper"
    mkIconViewMoveCursorCallback :: IconViewMoveCursorCallbackC -> IO (FunPtr IconViewMoveCursorCallbackC)

iconViewMoveCursorClosure :: IconViewMoveCursorCallback -> IO Closure
iconViewMoveCursorClosure cb = newCClosure =<< mkIconViewMoveCursorCallback wrapped
    where wrapped = iconViewMoveCursorCallbackWrapper cb

iconViewMoveCursorCallbackWrapper ::
    IconViewMoveCursorCallback ->
    Ptr () ->
    CUInt ->
    Int32 ->
    Ptr () ->
    IO CInt
iconViewMoveCursorCallbackWrapper _cb _ step count _ = do
    let step' = (toEnum . fromIntegral) step
    result <- _cb  step' count
    let result' = (fromIntegral . fromEnum) result
    return result'

onIconViewMoveCursor :: (GObject a, MonadIO m) => a -> IconViewMoveCursorCallback -> m SignalHandlerId
onIconViewMoveCursor obj cb = liftIO $ connectIconViewMoveCursor obj cb SignalConnectBefore
afterIconViewMoveCursor :: (GObject a, MonadIO m) => a -> IconViewMoveCursorCallback -> m SignalHandlerId
afterIconViewMoveCursor obj cb = connectIconViewMoveCursor obj cb SignalConnectAfter

connectIconViewMoveCursor :: (GObject a, MonadIO m) =>
                             a -> IconViewMoveCursorCallback -> SignalConnectMode -> m SignalHandlerId
connectIconViewMoveCursor obj cb after = liftIO $ do
    cb' <- mkIconViewMoveCursorCallback (iconViewMoveCursorCallbackWrapper cb)
    connectSignalFunPtr obj "move-cursor" cb' after

-- signal IconView::select-all
type IconViewSelectAllCallback =
    IO ()

noIconViewSelectAllCallback :: Maybe IconViewSelectAllCallback
noIconViewSelectAllCallback = Nothing

type IconViewSelectAllCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkIconViewSelectAllCallback :: IconViewSelectAllCallbackC -> IO (FunPtr IconViewSelectAllCallbackC)

iconViewSelectAllClosure :: IconViewSelectAllCallback -> IO Closure
iconViewSelectAllClosure cb = newCClosure =<< mkIconViewSelectAllCallback wrapped
    where wrapped = iconViewSelectAllCallbackWrapper cb

iconViewSelectAllCallbackWrapper ::
    IconViewSelectAllCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
iconViewSelectAllCallbackWrapper _cb _ _ = do
    _cb 

onIconViewSelectAll :: (GObject a, MonadIO m) => a -> IconViewSelectAllCallback -> m SignalHandlerId
onIconViewSelectAll obj cb = liftIO $ connectIconViewSelectAll obj cb SignalConnectBefore
afterIconViewSelectAll :: (GObject a, MonadIO m) => a -> IconViewSelectAllCallback -> m SignalHandlerId
afterIconViewSelectAll obj cb = connectIconViewSelectAll obj cb SignalConnectAfter

connectIconViewSelectAll :: (GObject a, MonadIO m) =>
                            a -> IconViewSelectAllCallback -> SignalConnectMode -> m SignalHandlerId
connectIconViewSelectAll obj cb after = liftIO $ do
    cb' <- mkIconViewSelectAllCallback (iconViewSelectAllCallbackWrapper cb)
    connectSignalFunPtr obj "select-all" cb' after

-- signal IconView::select-cursor-item
type IconViewSelectCursorItemCallback =
    IO ()

noIconViewSelectCursorItemCallback :: Maybe IconViewSelectCursorItemCallback
noIconViewSelectCursorItemCallback = Nothing

type IconViewSelectCursorItemCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkIconViewSelectCursorItemCallback :: IconViewSelectCursorItemCallbackC -> IO (FunPtr IconViewSelectCursorItemCallbackC)

iconViewSelectCursorItemClosure :: IconViewSelectCursorItemCallback -> IO Closure
iconViewSelectCursorItemClosure cb = newCClosure =<< mkIconViewSelectCursorItemCallback wrapped
    where wrapped = iconViewSelectCursorItemCallbackWrapper cb

iconViewSelectCursorItemCallbackWrapper ::
    IconViewSelectCursorItemCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
iconViewSelectCursorItemCallbackWrapper _cb _ _ = do
    _cb 

onIconViewSelectCursorItem :: (GObject a, MonadIO m) => a -> IconViewSelectCursorItemCallback -> m SignalHandlerId
onIconViewSelectCursorItem obj cb = liftIO $ connectIconViewSelectCursorItem obj cb SignalConnectBefore
afterIconViewSelectCursorItem :: (GObject a, MonadIO m) => a -> IconViewSelectCursorItemCallback -> m SignalHandlerId
afterIconViewSelectCursorItem obj cb = connectIconViewSelectCursorItem obj cb SignalConnectAfter

connectIconViewSelectCursorItem :: (GObject a, MonadIO m) =>
                                   a -> IconViewSelectCursorItemCallback -> SignalConnectMode -> m SignalHandlerId
connectIconViewSelectCursorItem obj cb after = liftIO $ do
    cb' <- mkIconViewSelectCursorItemCallback (iconViewSelectCursorItemCallbackWrapper cb)
    connectSignalFunPtr obj "select-cursor-item" cb' after

-- signal IconView::selection-changed
type IconViewSelectionChangedCallback =
    IO ()

noIconViewSelectionChangedCallback :: Maybe IconViewSelectionChangedCallback
noIconViewSelectionChangedCallback = Nothing

type IconViewSelectionChangedCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkIconViewSelectionChangedCallback :: IconViewSelectionChangedCallbackC -> IO (FunPtr IconViewSelectionChangedCallbackC)

iconViewSelectionChangedClosure :: IconViewSelectionChangedCallback -> IO Closure
iconViewSelectionChangedClosure cb = newCClosure =<< mkIconViewSelectionChangedCallback wrapped
    where wrapped = iconViewSelectionChangedCallbackWrapper cb

iconViewSelectionChangedCallbackWrapper ::
    IconViewSelectionChangedCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
iconViewSelectionChangedCallbackWrapper _cb _ _ = do
    _cb 

onIconViewSelectionChanged :: (GObject a, MonadIO m) => a -> IconViewSelectionChangedCallback -> m SignalHandlerId
onIconViewSelectionChanged obj cb = liftIO $ connectIconViewSelectionChanged obj cb SignalConnectBefore
afterIconViewSelectionChanged :: (GObject a, MonadIO m) => a -> IconViewSelectionChangedCallback -> m SignalHandlerId
afterIconViewSelectionChanged obj cb = connectIconViewSelectionChanged obj cb SignalConnectAfter

connectIconViewSelectionChanged :: (GObject a, MonadIO m) =>
                                   a -> IconViewSelectionChangedCallback -> SignalConnectMode -> m SignalHandlerId
connectIconViewSelectionChanged obj cb after = liftIO $ do
    cb' <- mkIconViewSelectionChangedCallback (iconViewSelectionChangedCallbackWrapper cb)
    connectSignalFunPtr obj "selection-changed" cb' after

-- signal IconView::toggle-cursor-item
type IconViewToggleCursorItemCallback =
    IO ()

noIconViewToggleCursorItemCallback :: Maybe IconViewToggleCursorItemCallback
noIconViewToggleCursorItemCallback = Nothing

type IconViewToggleCursorItemCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkIconViewToggleCursorItemCallback :: IconViewToggleCursorItemCallbackC -> IO (FunPtr IconViewToggleCursorItemCallbackC)

iconViewToggleCursorItemClosure :: IconViewToggleCursorItemCallback -> IO Closure
iconViewToggleCursorItemClosure cb = newCClosure =<< mkIconViewToggleCursorItemCallback wrapped
    where wrapped = iconViewToggleCursorItemCallbackWrapper cb

iconViewToggleCursorItemCallbackWrapper ::
    IconViewToggleCursorItemCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
iconViewToggleCursorItemCallbackWrapper _cb _ _ = do
    _cb 

onIconViewToggleCursorItem :: (GObject a, MonadIO m) => a -> IconViewToggleCursorItemCallback -> m SignalHandlerId
onIconViewToggleCursorItem obj cb = liftIO $ connectIconViewToggleCursorItem obj cb SignalConnectBefore
afterIconViewToggleCursorItem :: (GObject a, MonadIO m) => a -> IconViewToggleCursorItemCallback -> m SignalHandlerId
afterIconViewToggleCursorItem obj cb = connectIconViewToggleCursorItem obj cb SignalConnectAfter

connectIconViewToggleCursorItem :: (GObject a, MonadIO m) =>
                                   a -> IconViewToggleCursorItemCallback -> SignalConnectMode -> m SignalHandlerId
connectIconViewToggleCursorItem obj cb after = liftIO $ do
    cb' <- mkIconViewToggleCursorItemCallback (iconViewToggleCursorItemCallbackWrapper cb)
    connectSignalFunPtr obj "toggle-cursor-item" cb' after

-- signal IconView::unselect-all
type IconViewUnselectAllCallback =
    IO ()

noIconViewUnselectAllCallback :: Maybe IconViewUnselectAllCallback
noIconViewUnselectAllCallback = Nothing

type IconViewUnselectAllCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkIconViewUnselectAllCallback :: IconViewUnselectAllCallbackC -> IO (FunPtr IconViewUnselectAllCallbackC)

iconViewUnselectAllClosure :: IconViewUnselectAllCallback -> IO Closure
iconViewUnselectAllClosure cb = newCClosure =<< mkIconViewUnselectAllCallback wrapped
    where wrapped = iconViewUnselectAllCallbackWrapper cb

iconViewUnselectAllCallbackWrapper ::
    IconViewUnselectAllCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
iconViewUnselectAllCallbackWrapper _cb _ _ = do
    _cb 

onIconViewUnselectAll :: (GObject a, MonadIO m) => a -> IconViewUnselectAllCallback -> m SignalHandlerId
onIconViewUnselectAll obj cb = liftIO $ connectIconViewUnselectAll obj cb SignalConnectBefore
afterIconViewUnselectAll :: (GObject a, MonadIO m) => a -> IconViewUnselectAllCallback -> m SignalHandlerId
afterIconViewUnselectAll obj cb = connectIconViewUnselectAll obj cb SignalConnectAfter

connectIconViewUnselectAll :: (GObject a, MonadIO m) =>
                              a -> IconViewUnselectAllCallback -> SignalConnectMode -> m SignalHandlerId
connectIconViewUnselectAll obj cb after = liftIO $ do
    cb' <- mkIconViewUnselectAllCallback (iconViewUnselectAllCallbackWrapper cb)
    connectSignalFunPtr obj "unselect-all" cb' after

-- VVV Prop "activate-on-single-click"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewActivateOnSingleClick :: (MonadIO m, IconViewK o) => o -> m Bool
getIconViewActivateOnSingleClick obj = liftIO $ getObjectPropertyBool obj "activate-on-single-click"

setIconViewActivateOnSingleClick :: (MonadIO m, IconViewK o) => o -> Bool -> m ()
setIconViewActivateOnSingleClick obj val = liftIO $ setObjectPropertyBool obj "activate-on-single-click" val

constructIconViewActivateOnSingleClick :: Bool -> IO ([Char], GValue)
constructIconViewActivateOnSingleClick val = constructObjectPropertyBool "activate-on-single-click" val

data IconViewActivateOnSingleClickPropertyInfo
instance AttrInfo IconViewActivateOnSingleClickPropertyInfo where
    type AttrAllowedOps IconViewActivateOnSingleClickPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewActivateOnSingleClickPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint IconViewActivateOnSingleClickPropertyInfo = IconViewK
    type AttrGetType IconViewActivateOnSingleClickPropertyInfo = Bool
    type AttrLabel IconViewActivateOnSingleClickPropertyInfo = "IconView::activate-on-single-click"
    attrGet _ = getIconViewActivateOnSingleClick
    attrSet _ = setIconViewActivateOnSingleClick
    attrConstruct _ = constructIconViewActivateOnSingleClick

-- VVV Prop "cell-area"
   -- Type: TInterface "Gtk" "CellArea"
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]

getIconViewCellArea :: (MonadIO m, IconViewK o) => o -> m CellArea
getIconViewCellArea obj = liftIO $ getObjectPropertyObject obj "cell-area" CellArea

constructIconViewCellArea :: (CellAreaK a) => a -> IO ([Char], GValue)
constructIconViewCellArea val = constructObjectPropertyObject "cell-area" val

data IconViewCellAreaPropertyInfo
instance AttrInfo IconViewCellAreaPropertyInfo where
    type AttrAllowedOps IconViewCellAreaPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewCellAreaPropertyInfo = CellAreaK
    type AttrBaseTypeConstraint IconViewCellAreaPropertyInfo = IconViewK
    type AttrGetType IconViewCellAreaPropertyInfo = CellArea
    type AttrLabel IconViewCellAreaPropertyInfo = "IconView::cell-area"
    attrGet _ = getIconViewCellArea
    attrSet _ = undefined
    attrConstruct _ = constructIconViewCellArea

-- VVV Prop "column-spacing"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewColumnSpacing :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewColumnSpacing obj = liftIO $ getObjectPropertyCInt obj "column-spacing"

setIconViewColumnSpacing :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewColumnSpacing obj val = liftIO $ setObjectPropertyCInt obj "column-spacing" val

constructIconViewColumnSpacing :: Int32 -> IO ([Char], GValue)
constructIconViewColumnSpacing val = constructObjectPropertyCInt "column-spacing" val

data IconViewColumnSpacingPropertyInfo
instance AttrInfo IconViewColumnSpacingPropertyInfo where
    type AttrAllowedOps IconViewColumnSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewColumnSpacingPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewColumnSpacingPropertyInfo = IconViewK
    type AttrGetType IconViewColumnSpacingPropertyInfo = Int32
    type AttrLabel IconViewColumnSpacingPropertyInfo = "IconView::column-spacing"
    attrGet _ = getIconViewColumnSpacing
    attrSet _ = setIconViewColumnSpacing
    attrConstruct _ = constructIconViewColumnSpacing

-- VVV Prop "columns"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewColumns :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewColumns obj = liftIO $ getObjectPropertyCInt obj "columns"

setIconViewColumns :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewColumns obj val = liftIO $ setObjectPropertyCInt obj "columns" val

constructIconViewColumns :: Int32 -> IO ([Char], GValue)
constructIconViewColumns val = constructObjectPropertyCInt "columns" val

data IconViewColumnsPropertyInfo
instance AttrInfo IconViewColumnsPropertyInfo where
    type AttrAllowedOps IconViewColumnsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewColumnsPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewColumnsPropertyInfo = IconViewK
    type AttrGetType IconViewColumnsPropertyInfo = Int32
    type AttrLabel IconViewColumnsPropertyInfo = "IconView::columns"
    attrGet _ = getIconViewColumns
    attrSet _ = setIconViewColumns
    attrConstruct _ = constructIconViewColumns

-- VVV Prop "item-orientation"
   -- Type: TInterface "Gtk" "Orientation"
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewItemOrientation :: (MonadIO m, IconViewK o) => o -> m Orientation
getIconViewItemOrientation obj = liftIO $ getObjectPropertyEnum obj "item-orientation"

setIconViewItemOrientation :: (MonadIO m, IconViewK o) => o -> Orientation -> m ()
setIconViewItemOrientation obj val = liftIO $ setObjectPropertyEnum obj "item-orientation" val

constructIconViewItemOrientation :: Orientation -> IO ([Char], GValue)
constructIconViewItemOrientation val = constructObjectPropertyEnum "item-orientation" val

data IconViewItemOrientationPropertyInfo
instance AttrInfo IconViewItemOrientationPropertyInfo where
    type AttrAllowedOps IconViewItemOrientationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewItemOrientationPropertyInfo = (~) Orientation
    type AttrBaseTypeConstraint IconViewItemOrientationPropertyInfo = IconViewK
    type AttrGetType IconViewItemOrientationPropertyInfo = Orientation
    type AttrLabel IconViewItemOrientationPropertyInfo = "IconView::item-orientation"
    attrGet _ = getIconViewItemOrientation
    attrSet _ = setIconViewItemOrientation
    attrConstruct _ = constructIconViewItemOrientation

-- VVV Prop "item-padding"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewItemPadding :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewItemPadding obj = liftIO $ getObjectPropertyCInt obj "item-padding"

setIconViewItemPadding :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewItemPadding obj val = liftIO $ setObjectPropertyCInt obj "item-padding" val

constructIconViewItemPadding :: Int32 -> IO ([Char], GValue)
constructIconViewItemPadding val = constructObjectPropertyCInt "item-padding" val

data IconViewItemPaddingPropertyInfo
instance AttrInfo IconViewItemPaddingPropertyInfo where
    type AttrAllowedOps IconViewItemPaddingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewItemPaddingPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewItemPaddingPropertyInfo = IconViewK
    type AttrGetType IconViewItemPaddingPropertyInfo = Int32
    type AttrLabel IconViewItemPaddingPropertyInfo = "IconView::item-padding"
    attrGet _ = getIconViewItemPadding
    attrSet _ = setIconViewItemPadding
    attrConstruct _ = constructIconViewItemPadding

-- VVV Prop "item-width"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewItemWidth :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewItemWidth obj = liftIO $ getObjectPropertyCInt obj "item-width"

setIconViewItemWidth :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewItemWidth obj val = liftIO $ setObjectPropertyCInt obj "item-width" val

constructIconViewItemWidth :: Int32 -> IO ([Char], GValue)
constructIconViewItemWidth val = constructObjectPropertyCInt "item-width" val

data IconViewItemWidthPropertyInfo
instance AttrInfo IconViewItemWidthPropertyInfo where
    type AttrAllowedOps IconViewItemWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewItemWidthPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewItemWidthPropertyInfo = IconViewK
    type AttrGetType IconViewItemWidthPropertyInfo = Int32
    type AttrLabel IconViewItemWidthPropertyInfo = "IconView::item-width"
    attrGet _ = getIconViewItemWidth
    attrSet _ = setIconViewItemWidth
    attrConstruct _ = constructIconViewItemWidth

-- VVV Prop "margin"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewMargin :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewMargin obj = liftIO $ getObjectPropertyCInt obj "margin"

setIconViewMargin :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewMargin obj val = liftIO $ setObjectPropertyCInt obj "margin" val

constructIconViewMargin :: Int32 -> IO ([Char], GValue)
constructIconViewMargin val = constructObjectPropertyCInt "margin" val

data IconViewMarginPropertyInfo
instance AttrInfo IconViewMarginPropertyInfo where
    type AttrAllowedOps IconViewMarginPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewMarginPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewMarginPropertyInfo = IconViewK
    type AttrGetType IconViewMarginPropertyInfo = Int32
    type AttrLabel IconViewMarginPropertyInfo = "IconView::margin"
    attrGet _ = getIconViewMargin
    attrSet _ = setIconViewMargin
    attrConstruct _ = constructIconViewMargin

-- VVV Prop "markup-column"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewMarkupColumn :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewMarkupColumn obj = liftIO $ getObjectPropertyCInt obj "markup-column"

setIconViewMarkupColumn :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewMarkupColumn obj val = liftIO $ setObjectPropertyCInt obj "markup-column" val

constructIconViewMarkupColumn :: Int32 -> IO ([Char], GValue)
constructIconViewMarkupColumn val = constructObjectPropertyCInt "markup-column" val

data IconViewMarkupColumnPropertyInfo
instance AttrInfo IconViewMarkupColumnPropertyInfo where
    type AttrAllowedOps IconViewMarkupColumnPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewMarkupColumnPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewMarkupColumnPropertyInfo = IconViewK
    type AttrGetType IconViewMarkupColumnPropertyInfo = Int32
    type AttrLabel IconViewMarkupColumnPropertyInfo = "IconView::markup-column"
    attrGet _ = getIconViewMarkupColumn
    attrSet _ = setIconViewMarkupColumn
    attrConstruct _ = constructIconViewMarkupColumn

-- VVV Prop "model"
   -- Type: TInterface "Gtk" "TreeModel"
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewModel :: (MonadIO m, IconViewK o) => o -> m TreeModel
getIconViewModel obj = liftIO $ getObjectPropertyObject obj "model" TreeModel

setIconViewModel :: (MonadIO m, IconViewK o, TreeModelK a) => o -> a -> m ()
setIconViewModel obj val = liftIO $ setObjectPropertyObject obj "model" val

constructIconViewModel :: (TreeModelK a) => a -> IO ([Char], GValue)
constructIconViewModel val = constructObjectPropertyObject "model" val

data IconViewModelPropertyInfo
instance AttrInfo IconViewModelPropertyInfo where
    type AttrAllowedOps IconViewModelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewModelPropertyInfo = TreeModelK
    type AttrBaseTypeConstraint IconViewModelPropertyInfo = IconViewK
    type AttrGetType IconViewModelPropertyInfo = TreeModel
    type AttrLabel IconViewModelPropertyInfo = "IconView::model"
    attrGet _ = getIconViewModel
    attrSet _ = setIconViewModel
    attrConstruct _ = constructIconViewModel

-- VVV Prop "pixbuf-column"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewPixbufColumn :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewPixbufColumn obj = liftIO $ getObjectPropertyCInt obj "pixbuf-column"

setIconViewPixbufColumn :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewPixbufColumn obj val = liftIO $ setObjectPropertyCInt obj "pixbuf-column" val

constructIconViewPixbufColumn :: Int32 -> IO ([Char], GValue)
constructIconViewPixbufColumn val = constructObjectPropertyCInt "pixbuf-column" val

data IconViewPixbufColumnPropertyInfo
instance AttrInfo IconViewPixbufColumnPropertyInfo where
    type AttrAllowedOps IconViewPixbufColumnPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewPixbufColumnPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewPixbufColumnPropertyInfo = IconViewK
    type AttrGetType IconViewPixbufColumnPropertyInfo = Int32
    type AttrLabel IconViewPixbufColumnPropertyInfo = "IconView::pixbuf-column"
    attrGet _ = getIconViewPixbufColumn
    attrSet _ = setIconViewPixbufColumn
    attrConstruct _ = constructIconViewPixbufColumn

-- VVV Prop "reorderable"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewReorderable :: (MonadIO m, IconViewK o) => o -> m Bool
getIconViewReorderable obj = liftIO $ getObjectPropertyBool obj "reorderable"

setIconViewReorderable :: (MonadIO m, IconViewK o) => o -> Bool -> m ()
setIconViewReorderable obj val = liftIO $ setObjectPropertyBool obj "reorderable" val

constructIconViewReorderable :: Bool -> IO ([Char], GValue)
constructIconViewReorderable val = constructObjectPropertyBool "reorderable" val

data IconViewReorderablePropertyInfo
instance AttrInfo IconViewReorderablePropertyInfo where
    type AttrAllowedOps IconViewReorderablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewReorderablePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint IconViewReorderablePropertyInfo = IconViewK
    type AttrGetType IconViewReorderablePropertyInfo = Bool
    type AttrLabel IconViewReorderablePropertyInfo = "IconView::reorderable"
    attrGet _ = getIconViewReorderable
    attrSet _ = setIconViewReorderable
    attrConstruct _ = constructIconViewReorderable

-- VVV Prop "row-spacing"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewRowSpacing :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewRowSpacing obj = liftIO $ getObjectPropertyCInt obj "row-spacing"

setIconViewRowSpacing :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewRowSpacing obj val = liftIO $ setObjectPropertyCInt obj "row-spacing" val

constructIconViewRowSpacing :: Int32 -> IO ([Char], GValue)
constructIconViewRowSpacing val = constructObjectPropertyCInt "row-spacing" val

data IconViewRowSpacingPropertyInfo
instance AttrInfo IconViewRowSpacingPropertyInfo where
    type AttrAllowedOps IconViewRowSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewRowSpacingPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewRowSpacingPropertyInfo = IconViewK
    type AttrGetType IconViewRowSpacingPropertyInfo = Int32
    type AttrLabel IconViewRowSpacingPropertyInfo = "IconView::row-spacing"
    attrGet _ = getIconViewRowSpacing
    attrSet _ = setIconViewRowSpacing
    attrConstruct _ = constructIconViewRowSpacing

-- VVV Prop "selection-mode"
   -- Type: TInterface "Gtk" "SelectionMode"
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewSelectionMode :: (MonadIO m, IconViewK o) => o -> m SelectionMode
getIconViewSelectionMode obj = liftIO $ getObjectPropertyEnum obj "selection-mode"

setIconViewSelectionMode :: (MonadIO m, IconViewK o) => o -> SelectionMode -> m ()
setIconViewSelectionMode obj val = liftIO $ setObjectPropertyEnum obj "selection-mode" val

constructIconViewSelectionMode :: SelectionMode -> IO ([Char], GValue)
constructIconViewSelectionMode val = constructObjectPropertyEnum "selection-mode" val

data IconViewSelectionModePropertyInfo
instance AttrInfo IconViewSelectionModePropertyInfo where
    type AttrAllowedOps IconViewSelectionModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewSelectionModePropertyInfo = (~) SelectionMode
    type AttrBaseTypeConstraint IconViewSelectionModePropertyInfo = IconViewK
    type AttrGetType IconViewSelectionModePropertyInfo = SelectionMode
    type AttrLabel IconViewSelectionModePropertyInfo = "IconView::selection-mode"
    attrGet _ = getIconViewSelectionMode
    attrSet _ = setIconViewSelectionMode
    attrConstruct _ = constructIconViewSelectionMode

-- VVV Prop "spacing"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewSpacing :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewSpacing obj = liftIO $ getObjectPropertyCInt obj "spacing"

setIconViewSpacing :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewSpacing obj val = liftIO $ setObjectPropertyCInt obj "spacing" val

constructIconViewSpacing :: Int32 -> IO ([Char], GValue)
constructIconViewSpacing val = constructObjectPropertyCInt "spacing" val

data IconViewSpacingPropertyInfo
instance AttrInfo IconViewSpacingPropertyInfo where
    type AttrAllowedOps IconViewSpacingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewSpacingPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewSpacingPropertyInfo = IconViewK
    type AttrGetType IconViewSpacingPropertyInfo = Int32
    type AttrLabel IconViewSpacingPropertyInfo = "IconView::spacing"
    attrGet _ = getIconViewSpacing
    attrSet _ = setIconViewSpacing
    attrConstruct _ = constructIconViewSpacing

-- VVV Prop "text-column"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewTextColumn :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewTextColumn obj = liftIO $ getObjectPropertyCInt obj "text-column"

setIconViewTextColumn :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewTextColumn obj val = liftIO $ setObjectPropertyCInt obj "text-column" val

constructIconViewTextColumn :: Int32 -> IO ([Char], GValue)
constructIconViewTextColumn val = constructObjectPropertyCInt "text-column" val

data IconViewTextColumnPropertyInfo
instance AttrInfo IconViewTextColumnPropertyInfo where
    type AttrAllowedOps IconViewTextColumnPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewTextColumnPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewTextColumnPropertyInfo = IconViewK
    type AttrGetType IconViewTextColumnPropertyInfo = Int32
    type AttrLabel IconViewTextColumnPropertyInfo = "IconView::text-column"
    attrGet _ = getIconViewTextColumn
    attrSet _ = setIconViewTextColumn
    attrConstruct _ = constructIconViewTextColumn

-- VVV Prop "tooltip-column"
   -- Type: TBasicType TInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getIconViewTooltipColumn :: (MonadIO m, IconViewK o) => o -> m Int32
getIconViewTooltipColumn obj = liftIO $ getObjectPropertyCInt obj "tooltip-column"

setIconViewTooltipColumn :: (MonadIO m, IconViewK o) => o -> Int32 -> m ()
setIconViewTooltipColumn obj val = liftIO $ setObjectPropertyCInt obj "tooltip-column" val

constructIconViewTooltipColumn :: Int32 -> IO ([Char], GValue)
constructIconViewTooltipColumn val = constructObjectPropertyCInt "tooltip-column" val

data IconViewTooltipColumnPropertyInfo
instance AttrInfo IconViewTooltipColumnPropertyInfo where
    type AttrAllowedOps IconViewTooltipColumnPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint IconViewTooltipColumnPropertyInfo = (~) Int32
    type AttrBaseTypeConstraint IconViewTooltipColumnPropertyInfo = IconViewK
    type AttrGetType IconViewTooltipColumnPropertyInfo = Int32
    type AttrLabel IconViewTooltipColumnPropertyInfo = "IconView::tooltip-column"
    attrGet _ = getIconViewTooltipColumn
    attrSet _ = setIconViewTooltipColumn
    attrConstruct _ = constructIconViewTooltipColumn

type instance AttributeList IconView = IconViewAttributeList
type IconViewAttributeList = ('[ '("activate-on-single-click", IconViewActivateOnSingleClickPropertyInfo), '("app-paintable", WidgetAppPaintablePropertyInfo), '("border-width", ContainerBorderWidthPropertyInfo), '("can-default", WidgetCanDefaultPropertyInfo), '("can-focus", WidgetCanFocusPropertyInfo), '("cell-area", IconViewCellAreaPropertyInfo), '("child", ContainerChildPropertyInfo), '("column-spacing", IconViewColumnSpacingPropertyInfo), '("columns", IconViewColumnsPropertyInfo), '("composite-child", WidgetCompositeChildPropertyInfo), '("double-buffered", WidgetDoubleBufferedPropertyInfo), '("events", WidgetEventsPropertyInfo), '("expand", WidgetExpandPropertyInfo), '("hadjustment", ScrollableHadjustmentPropertyInfo), '("halign", WidgetHalignPropertyInfo), '("has-default", WidgetHasDefaultPropertyInfo), '("has-focus", WidgetHasFocusPropertyInfo), '("has-tooltip", WidgetHasTooltipPropertyInfo), '("height-request", WidgetHeightRequestPropertyInfo), '("hexpand", WidgetHexpandPropertyInfo), '("hexpand-set", WidgetHexpandSetPropertyInfo), '("hscroll-policy", ScrollableHscrollPolicyPropertyInfo), '("is-focus", WidgetIsFocusPropertyInfo), '("item-orientation", IconViewItemOrientationPropertyInfo), '("item-padding", IconViewItemPaddingPropertyInfo), '("item-width", IconViewItemWidthPropertyInfo), '("margin", IconViewMarginPropertyInfo), '("margin-bottom", WidgetMarginBottomPropertyInfo), '("margin-end", WidgetMarginEndPropertyInfo), '("margin-left", WidgetMarginLeftPropertyInfo), '("margin-right", WidgetMarginRightPropertyInfo), '("margin-start", WidgetMarginStartPropertyInfo), '("margin-top", WidgetMarginTopPropertyInfo), '("markup-column", IconViewMarkupColumnPropertyInfo), '("model", IconViewModelPropertyInfo), '("name", WidgetNamePropertyInfo), '("no-show-all", WidgetNoShowAllPropertyInfo), '("opacity", WidgetOpacityPropertyInfo), '("parent", WidgetParentPropertyInfo), '("pixbuf-column", IconViewPixbufColumnPropertyInfo), '("receives-default", WidgetReceivesDefaultPropertyInfo), '("reorderable", IconViewReorderablePropertyInfo), '("resize-mode", ContainerResizeModePropertyInfo), '("row-spacing", IconViewRowSpacingPropertyInfo), '("scale-factor", WidgetScaleFactorPropertyInfo), '("selection-mode", IconViewSelectionModePropertyInfo), '("sensitive", WidgetSensitivePropertyInfo), '("spacing", IconViewSpacingPropertyInfo), '("style", WidgetStylePropertyInfo), '("text-column", IconViewTextColumnPropertyInfo), '("tooltip-column", IconViewTooltipColumnPropertyInfo), '("tooltip-markup", WidgetTooltipMarkupPropertyInfo), '("tooltip-text", WidgetTooltipTextPropertyInfo), '("vadjustment", ScrollableVadjustmentPropertyInfo), '("valign", WidgetValignPropertyInfo), '("vexpand", WidgetVexpandPropertyInfo), '("vexpand-set", WidgetVexpandSetPropertyInfo), '("visible", WidgetVisiblePropertyInfo), '("vscroll-policy", ScrollableVscrollPolicyPropertyInfo), '("width-request", WidgetWidthRequestPropertyInfo), '("window", WidgetWindowPropertyInfo)] :: [(Symbol, *)])

data IconViewActivateCursorItemSignalInfo
instance SignalInfo IconViewActivateCursorItemSignalInfo where
    type HaskellCallbackType IconViewActivateCursorItemSignalInfo = IconViewActivateCursorItemCallback
    connectSignal _ = connectIconViewActivateCursorItem

data IconViewItemActivatedSignalInfo
instance SignalInfo IconViewItemActivatedSignalInfo where
    type HaskellCallbackType IconViewItemActivatedSignalInfo = IconViewItemActivatedCallback
    connectSignal _ = connectIconViewItemActivated

data IconViewMoveCursorSignalInfo
instance SignalInfo IconViewMoveCursorSignalInfo where
    type HaskellCallbackType IconViewMoveCursorSignalInfo = IconViewMoveCursorCallback
    connectSignal _ = connectIconViewMoveCursor

data IconViewSelectAllSignalInfo
instance SignalInfo IconViewSelectAllSignalInfo where
    type HaskellCallbackType IconViewSelectAllSignalInfo = IconViewSelectAllCallback
    connectSignal _ = connectIconViewSelectAll

data IconViewSelectCursorItemSignalInfo
instance SignalInfo IconViewSelectCursorItemSignalInfo where
    type HaskellCallbackType IconViewSelectCursorItemSignalInfo = IconViewSelectCursorItemCallback
    connectSignal _ = connectIconViewSelectCursorItem

data IconViewSelectionChangedSignalInfo
instance SignalInfo IconViewSelectionChangedSignalInfo where
    type HaskellCallbackType IconViewSelectionChangedSignalInfo = IconViewSelectionChangedCallback
    connectSignal _ = connectIconViewSelectionChanged

data IconViewToggleCursorItemSignalInfo
instance SignalInfo IconViewToggleCursorItemSignalInfo where
    type HaskellCallbackType IconViewToggleCursorItemSignalInfo = IconViewToggleCursorItemCallback
    connectSignal _ = connectIconViewToggleCursorItem

data IconViewUnselectAllSignalInfo
instance SignalInfo IconViewUnselectAllSignalInfo where
    type HaskellCallbackType IconViewUnselectAllSignalInfo = IconViewUnselectAllCallback
    connectSignal _ = connectIconViewUnselectAll

type instance SignalList IconView = IconViewSignalList
type IconViewSignalList = ('[ '("accel-closures-changed", WidgetAccelClosuresChangedSignalInfo), '("activate-cursor-item", IconViewActivateCursorItemSignalInfo), '("add", ContainerAddSignalInfo), '("button-press-event", WidgetButtonPressEventSignalInfo), '("button-release-event", WidgetButtonReleaseEventSignalInfo), '("can-activate-accel", WidgetCanActivateAccelSignalInfo), '("check-resize", ContainerCheckResizeSignalInfo), '("child-notify", WidgetChildNotifySignalInfo), '("composited-changed", WidgetCompositedChangedSignalInfo), '("configure-event", WidgetConfigureEventSignalInfo), '("damage-event", WidgetDamageEventSignalInfo), '("delete-event", WidgetDeleteEventSignalInfo), '("destroy", WidgetDestroySignalInfo), '("destroy-event", WidgetDestroyEventSignalInfo), '("direction-changed", WidgetDirectionChangedSignalInfo), '("drag-begin", WidgetDragBeginSignalInfo), '("drag-data-delete", WidgetDragDataDeleteSignalInfo), '("drag-data-get", WidgetDragDataGetSignalInfo), '("drag-data-received", WidgetDragDataReceivedSignalInfo), '("drag-drop", WidgetDragDropSignalInfo), '("drag-end", WidgetDragEndSignalInfo), '("drag-failed", WidgetDragFailedSignalInfo), '("drag-leave", WidgetDragLeaveSignalInfo), '("drag-motion", WidgetDragMotionSignalInfo), '("draw", WidgetDrawSignalInfo), '("enter-notify-event", WidgetEnterNotifyEventSignalInfo), '("event", WidgetEventSignalInfo), '("event-after", WidgetEventAfterSignalInfo), '("focus", WidgetFocusSignalInfo), '("focus-in-event", WidgetFocusInEventSignalInfo), '("focus-out-event", WidgetFocusOutEventSignalInfo), '("grab-broken-event", WidgetGrabBrokenEventSignalInfo), '("grab-focus", WidgetGrabFocusSignalInfo), '("grab-notify", WidgetGrabNotifySignalInfo), '("hide", WidgetHideSignalInfo), '("hierarchy-changed", WidgetHierarchyChangedSignalInfo), '("item-activated", IconViewItemActivatedSignalInfo), '("key-press-event", WidgetKeyPressEventSignalInfo), '("key-release-event", WidgetKeyReleaseEventSignalInfo), '("keynav-failed", WidgetKeynavFailedSignalInfo), '("leave-notify-event", WidgetLeaveNotifyEventSignalInfo), '("map", WidgetMapSignalInfo), '("map-event", WidgetMapEventSignalInfo), '("mnemonic-activate", WidgetMnemonicActivateSignalInfo), '("motion-notify-event", WidgetMotionNotifyEventSignalInfo), '("move-cursor", IconViewMoveCursorSignalInfo), '("move-focus", WidgetMoveFocusSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("parent-set", WidgetParentSetSignalInfo), '("popup-menu", WidgetPopupMenuSignalInfo), '("property-notify-event", WidgetPropertyNotifyEventSignalInfo), '("proximity-in-event", WidgetProximityInEventSignalInfo), '("proximity-out-event", WidgetProximityOutEventSignalInfo), '("query-tooltip", WidgetQueryTooltipSignalInfo), '("realize", WidgetRealizeSignalInfo), '("remove", ContainerRemoveSignalInfo), '("screen-changed", WidgetScreenChangedSignalInfo), '("scroll-event", WidgetScrollEventSignalInfo), '("select-all", IconViewSelectAllSignalInfo), '("select-cursor-item", IconViewSelectCursorItemSignalInfo), '("selection-changed", IconViewSelectionChangedSignalInfo), '("selection-clear-event", WidgetSelectionClearEventSignalInfo), '("selection-get", WidgetSelectionGetSignalInfo), '("selection-notify-event", WidgetSelectionNotifyEventSignalInfo), '("selection-received", WidgetSelectionReceivedSignalInfo), '("selection-request-event", WidgetSelectionRequestEventSignalInfo), '("set-focus-child", ContainerSetFocusChildSignalInfo), '("show", WidgetShowSignalInfo), '("show-help", WidgetShowHelpSignalInfo), '("size-allocate", WidgetSizeAllocateSignalInfo), '("state-changed", WidgetStateChangedSignalInfo), '("state-flags-changed", WidgetStateFlagsChangedSignalInfo), '("style-set", WidgetStyleSetSignalInfo), '("style-updated", WidgetStyleUpdatedSignalInfo), '("toggle-cursor-item", IconViewToggleCursorItemSignalInfo), '("touch-event", WidgetTouchEventSignalInfo), '("unmap", WidgetUnmapSignalInfo), '("unmap-event", WidgetUnmapEventSignalInfo), '("unrealize", WidgetUnrealizeSignalInfo), '("unselect-all", IconViewUnselectAllSignalInfo), '("visibility-notify-event", WidgetVisibilityNotifyEventSignalInfo), '("window-state-event", WidgetWindowStateEventSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method IconView::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Gtk" "IconView"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_new" gtk_icon_view_new :: 
    IO (Ptr IconView)


iconViewNew ::
    (MonadIO m) =>
    m IconView
iconViewNew  = liftIO $ do
    result <- gtk_icon_view_new
    checkUnexpectedReturnNULL "gtk_icon_view_new" result
    result' <- (newObject IconView) result
    return result'

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

foreign import ccall "gtk_icon_view_new_with_area" gtk_icon_view_new_with_area :: 
    Ptr CellArea ->                         -- area : TInterface "Gtk" "CellArea"
    IO (Ptr IconView)


iconViewNewWithArea ::
    (MonadIO m, CellAreaK a) =>
    a ->                                    -- area
    m IconView
iconViewNewWithArea area = liftIO $ do
    let area' = unsafeManagedPtrCastPtr area
    result <- gtk_icon_view_new_with_area area'
    checkUnexpectedReturnNULL "gtk_icon_view_new_with_area" result
    result' <- (newObject IconView) result
    touchManagedPtr area
    return result'

-- method IconView::new_with_model
-- method type : Constructor
-- Args : [Arg {argName = "model", argType = TInterface "Gtk" "TreeModel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "model", argType = TInterface "Gtk" "TreeModel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "IconView"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_new_with_model" gtk_icon_view_new_with_model :: 
    Ptr TreeModel ->                        -- model : TInterface "Gtk" "TreeModel"
    IO (Ptr IconView)


iconViewNewWithModel ::
    (MonadIO m, TreeModelK a) =>
    a ->                                    -- model
    m IconView
iconViewNewWithModel model = liftIO $ do
    let model' = unsafeManagedPtrCastPtr model
    result <- gtk_icon_view_new_with_model model'
    checkUnexpectedReturnNULL "gtk_icon_view_new_with_model" result
    result' <- (newObject IconView) result
    touchManagedPtr model
    return result'

-- method IconView::convert_widget_to_bin_window_coords
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "wx", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "wy", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bx", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "by", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "wx", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "wy", 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_icon_view_convert_widget_to_bin_window_coords" gtk_icon_view_convert_widget_to_bin_window_coords :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- wx : TBasicType TInt32
    Int32 ->                                -- wy : TBasicType TInt32
    Ptr Int32 ->                            -- bx : TBasicType TInt32
    Ptr Int32 ->                            -- by : TBasicType TInt32
    IO ()


iconViewConvertWidgetToBinWindowCoords ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- wx
    Int32 ->                                -- wy
    m (Int32,Int32)
iconViewConvertWidgetToBinWindowCoords _obj wx wy = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    bx <- allocMem :: IO (Ptr Int32)
    by <- allocMem :: IO (Ptr Int32)
    gtk_icon_view_convert_widget_to_bin_window_coords _obj' wx wy bx by
    bx' <- peek bx
    by' <- peek by
    touchManagedPtr _obj
    freeMem bx
    freeMem by
    return (bx', by')

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

foreign import ccall "gtk_icon_view_create_drag_icon" gtk_icon_view_create_drag_icon :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    IO (Ptr Cairo.Surface)


iconViewCreateDragIcon ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    m Cairo.Surface
iconViewCreateDragIcon _obj path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    result <- gtk_icon_view_create_drag_icon _obj' path'
    checkUnexpectedReturnNULL "gtk_icon_view_create_drag_icon" result
    result' <- (wrapBoxed Cairo.Surface) result
    touchManagedPtr _obj
    touchManagedPtr path
    return result'

-- method IconView::enable_model_drag_dest
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "targets", argType = TCArray False (-1) 2 (TInterface "Gtk" "TargetEntry"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n_targets", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "actions", argType = TInterface "Gdk" "DragAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "n_targets", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "targets", argType = TCArray False (-1) 2 (TInterface "Gtk" "TargetEntry"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "actions", argType = TInterface "Gdk" "DragAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_enable_model_drag_dest" gtk_icon_view_enable_model_drag_dest :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TargetEntry ->                      -- targets : TCArray False (-1) 2 (TInterface "Gtk" "TargetEntry")
    Int32 ->                                -- n_targets : TBasicType TInt32
    CUInt ->                                -- actions : TInterface "Gdk" "DragAction"
    IO ()


iconViewEnableModelDragDest ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    [TargetEntry] ->                        -- targets
    [Gdk.DragAction] ->                     -- actions
    m ()
iconViewEnableModelDragDest _obj targets actions = liftIO $ do
    let n_targets = fromIntegral $ length targets
    let _obj' = unsafeManagedPtrCastPtr _obj
    let targets' = map unsafeManagedPtrGetPtr targets
    targets'' <- packBlockArray 16 targets'
    let actions' = gflagsToWord actions
    gtk_icon_view_enable_model_drag_dest _obj' targets'' n_targets actions'
    touchManagedPtr _obj
    mapM_ touchManagedPtr targets
    freeMem targets''
    return ()

-- method IconView::enable_model_drag_source
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start_button_mask", argType = TInterface "Gdk" "ModifierType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "targets", argType = TCArray False (-1) 3 (TInterface "Gtk" "TargetEntry"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n_targets", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "actions", argType = TInterface "Gdk" "DragAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "n_targets", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start_button_mask", argType = TInterface "Gdk" "ModifierType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "targets", argType = TCArray False (-1) 3 (TInterface "Gtk" "TargetEntry"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "actions", argType = TInterface "Gdk" "DragAction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_enable_model_drag_source" gtk_icon_view_enable_model_drag_source :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    CUInt ->                                -- start_button_mask : TInterface "Gdk" "ModifierType"
    Ptr TargetEntry ->                      -- targets : TCArray False (-1) 3 (TInterface "Gtk" "TargetEntry")
    Int32 ->                                -- n_targets : TBasicType TInt32
    CUInt ->                                -- actions : TInterface "Gdk" "DragAction"
    IO ()


iconViewEnableModelDragSource ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    [Gdk.ModifierType] ->                   -- start_button_mask
    [TargetEntry] ->                        -- targets
    [Gdk.DragAction] ->                     -- actions
    m ()
iconViewEnableModelDragSource _obj start_button_mask targets actions = liftIO $ do
    let n_targets = fromIntegral $ length targets
    let _obj' = unsafeManagedPtrCastPtr _obj
    let start_button_mask' = gflagsToWord start_button_mask
    let targets' = map unsafeManagedPtrGetPtr targets
    targets'' <- packBlockArray 16 targets'
    let actions' = gflagsToWord actions
    gtk_icon_view_enable_model_drag_source _obj' start_button_mask' targets'' n_targets actions'
    touchManagedPtr _obj
    mapM_ touchManagedPtr targets
    freeMem targets''
    return ()

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

foreign import ccall "gtk_icon_view_get_activate_on_single_click" gtk_icon_view_get_activate_on_single_click :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO CInt


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

-- method IconView::get_cell_rect
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "rect", argType = TInterface "cairo" "RectangleInt", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_get_cell_rect" gtk_icon_view_get_cell_rect :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    Ptr CellRenderer ->                     -- cell : TInterface "Gtk" "CellRenderer"
    Ptr Cairo.RectangleInt ->               -- rect : TInterface "cairo" "RectangleInt"
    IO CInt


iconViewGetCellRect ::
    (MonadIO m, IconViewK a, CellRendererK b) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    Maybe (b) ->                            -- cell
    m (Bool,Cairo.RectangleInt)
iconViewGetCellRect _obj path cell = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    maybeCell <- case cell of
        Nothing -> return nullPtr
        Just jCell -> do
            let jCell' = unsafeManagedPtrCastPtr jCell
            return jCell'
    rect <- callocBoxedBytes 16 :: IO (Ptr Cairo.RectangleInt)
    result <- gtk_icon_view_get_cell_rect _obj' path' maybeCell rect
    let result' = (/= 0) result
    rect' <- (wrapBoxed Cairo.RectangleInt) rect
    touchManagedPtr _obj
    touchManagedPtr path
    whenJust cell touchManagedPtr
    return (result', rect')

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

foreign import ccall "gtk_icon_view_get_column_spacing" gtk_icon_view_get_column_spacing :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetColumnSpacing ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetColumnSpacing _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_column_spacing _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_columns" gtk_icon_view_get_columns :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetColumns ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetColumns _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_columns _obj'
    touchManagedPtr _obj
    return result

-- method IconView::get_cursor
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "cell", argType = TInterface "Gtk" "CellRenderer", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_get_cursor" gtk_icon_view_get_cursor :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr (Ptr TreePath) ->                   -- path : TInterface "Gtk" "TreePath"
    Ptr (Ptr CellRenderer) ->               -- cell : TInterface "Gtk" "CellRenderer"
    IO CInt


iconViewGetCursor ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m (Bool,TreePath,CellRenderer)
iconViewGetCursor _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    path <- allocMem :: IO (Ptr (Ptr TreePath))
    cell <- allocMem :: IO (Ptr (Ptr CellRenderer))
    result <- gtk_icon_view_get_cursor _obj' path cell
    let result' = (/= 0) result
    path' <- peek path
    path'' <- (wrapBoxed TreePath) path'
    cell' <- peek cell
    cell'' <- (newObject CellRenderer) cell'
    touchManagedPtr _obj
    freeMem path
    freeMem cell
    return (result', path'', cell'')

-- method IconView::get_dest_item_at_pos
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "drag_x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "drag_y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "pos", argType = TInterface "Gtk" "IconViewDropPosition", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "drag_x", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "drag_y", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_get_dest_item_at_pos" gtk_icon_view_get_dest_item_at_pos :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- drag_x : TBasicType TInt32
    Int32 ->                                -- drag_y : TBasicType TInt32
    Ptr (Ptr TreePath) ->                   -- path : TInterface "Gtk" "TreePath"
    Ptr CUInt ->                            -- pos : TInterface "Gtk" "IconViewDropPosition"
    IO CInt


iconViewGetDestItemAtPos ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- drag_x
    Int32 ->                                -- drag_y
    m (Bool,TreePath,IconViewDropPosition)
iconViewGetDestItemAtPos _obj drag_x drag_y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    path <- allocMem :: IO (Ptr (Ptr TreePath))
    pos <- allocMem :: IO (Ptr CUInt)
    result <- gtk_icon_view_get_dest_item_at_pos _obj' drag_x drag_y path pos
    let result' = (/= 0) result
    path' <- peek path
    path'' <- (wrapBoxed TreePath) path'
    pos' <- peek pos
    let pos'' = (toEnum . fromIntegral) pos'
    touchManagedPtr _obj
    freeMem path
    freeMem pos
    return (result', path'', pos'')

-- method IconView::get_drag_dest_item
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "pos", argType = TInterface "Gtk" "IconViewDropPosition", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_get_drag_dest_item" gtk_icon_view_get_drag_dest_item :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr (Ptr TreePath) ->                   -- path : TInterface "Gtk" "TreePath"
    Ptr CUInt ->                            -- pos : TInterface "Gtk" "IconViewDropPosition"
    IO ()


iconViewGetDragDestItem ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m (TreePath,IconViewDropPosition)
iconViewGetDragDestItem _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    path <- allocMem :: IO (Ptr (Ptr TreePath))
    pos <- allocMem :: IO (Ptr CUInt)
    gtk_icon_view_get_drag_dest_item _obj' path pos
    path' <- peek path
    path'' <- (wrapBoxed TreePath) path'
    pos' <- peek pos
    let pos'' = (toEnum . fromIntegral) pos'
    touchManagedPtr _obj
    freeMem path
    freeMem pos
    return (path'', pos'')

-- method IconView::get_item_at_pos
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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 = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "cell", argType = TInterface "Gtk" "CellRenderer", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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 : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_get_item_at_pos" gtk_icon_view_get_item_at_pos :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- x : TBasicType TInt32
    Int32 ->                                -- y : TBasicType TInt32
    Ptr (Ptr TreePath) ->                   -- path : TInterface "Gtk" "TreePath"
    Ptr (Ptr CellRenderer) ->               -- cell : TInterface "Gtk" "CellRenderer"
    IO CInt


iconViewGetItemAtPos ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- x
    Int32 ->                                -- y
    m (Bool,TreePath,CellRenderer)
iconViewGetItemAtPos _obj x y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    path <- allocMem :: IO (Ptr (Ptr TreePath))
    cell <- allocMem :: IO (Ptr (Ptr CellRenderer))
    result <- gtk_icon_view_get_item_at_pos _obj' x y path cell
    let result' = (/= 0) result
    path' <- peek path
    path'' <- (wrapBoxed TreePath) path'
    cell' <- peek cell
    cell'' <- (wrapObject CellRenderer) cell'
    touchManagedPtr _obj
    freeMem path
    freeMem cell
    return (result', path'', cell'')

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

foreign import ccall "gtk_icon_view_get_item_column" gtk_icon_view_get_item_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    IO Int32


iconViewGetItemColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    m Int32
iconViewGetItemColumn _obj path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    result <- gtk_icon_view_get_item_column _obj' path'
    touchManagedPtr _obj
    touchManagedPtr path
    return result

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

foreign import ccall "gtk_icon_view_get_item_orientation" gtk_icon_view_get_item_orientation :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO CUInt


iconViewGetItemOrientation ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Orientation
iconViewGetItemOrientation _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_item_orientation _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_icon_view_get_item_padding" gtk_icon_view_get_item_padding :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetItemPadding ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetItemPadding _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_item_padding _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_item_row" gtk_icon_view_get_item_row :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    IO Int32


iconViewGetItemRow ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    m Int32
iconViewGetItemRow _obj path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    result <- gtk_icon_view_get_item_row _obj' path'
    touchManagedPtr _obj
    touchManagedPtr path
    return result

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

foreign import ccall "gtk_icon_view_get_item_width" gtk_icon_view_get_item_width :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetItemWidth ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetItemWidth _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_item_width _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_margin" gtk_icon_view_get_margin :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetMargin ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetMargin _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_margin _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_markup_column" gtk_icon_view_get_markup_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetMarkupColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetMarkupColumn _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_markup_column _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_model" gtk_icon_view_get_model :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO (Ptr TreeModel)


iconViewGetModel ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m TreeModel
iconViewGetModel _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_model _obj'
    checkUnexpectedReturnNULL "gtk_icon_view_get_model" result
    result' <- (newObject TreeModel) result
    touchManagedPtr _obj
    return result'

-- method IconView::get_path_at_pos
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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" "TreePath"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_get_path_at_pos" gtk_icon_view_get_path_at_pos :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- x : TBasicType TInt32
    Int32 ->                                -- y : TBasicType TInt32
    IO (Ptr TreePath)


iconViewGetPathAtPos ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- x
    Int32 ->                                -- y
    m TreePath
iconViewGetPathAtPos _obj x y = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_path_at_pos _obj' x y
    checkUnexpectedReturnNULL "gtk_icon_view_get_path_at_pos" result
    result' <- (wrapBoxed TreePath) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_icon_view_get_pixbuf_column" gtk_icon_view_get_pixbuf_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetPixbufColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetPixbufColumn _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_pixbuf_column _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_reorderable" gtk_icon_view_get_reorderable :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO CInt


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

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

foreign import ccall "gtk_icon_view_get_row_spacing" gtk_icon_view_get_row_spacing :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetRowSpacing ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetRowSpacing _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_row_spacing _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_selected_items" gtk_icon_view_get_selected_items :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO (Ptr (GList (Ptr TreePath)))


iconViewGetSelectedItems ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m [TreePath]
iconViewGetSelectedItems _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_selected_items _obj'
    checkUnexpectedReturnNULL "gtk_icon_view_get_selected_items" result
    result' <- unpackGList result
    result'' <- mapM (wrapBoxed TreePath) result'
    g_list_free result
    touchManagedPtr _obj
    return result''

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

foreign import ccall "gtk_icon_view_get_selection_mode" gtk_icon_view_get_selection_mode :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO CUInt


iconViewGetSelectionMode ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m SelectionMode
iconViewGetSelectionMode _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_selection_mode _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "gtk_icon_view_get_spacing" gtk_icon_view_get_spacing :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetSpacing ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetSpacing _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_spacing _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_text_column" gtk_icon_view_get_text_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetTextColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetTextColumn _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_text_column _obj'
    touchManagedPtr _obj
    return result

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

foreign import ccall "gtk_icon_view_get_tooltip_column" gtk_icon_view_get_tooltip_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO Int32


iconViewGetTooltipColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m Int32
iconViewGetTooltipColumn _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_icon_view_get_tooltip_column _obj'
    touchManagedPtr _obj
    return result

-- method IconView::get_tooltip_context
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TInt32, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "keyboard_tip", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "model", argType = TInterface "Gtk" "TreeModel", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "iter", argType = TInterface "Gtk" "TreeIter", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TInt32, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "y", argType = TBasicType TInt32, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "keyboard_tip", 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_icon_view_get_tooltip_context" gtk_icon_view_get_tooltip_context :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr Int32 ->                            -- x : TBasicType TInt32
    Ptr Int32 ->                            -- y : TBasicType TInt32
    CInt ->                                 -- keyboard_tip : TBasicType TBoolean
    Ptr (Ptr TreeModel) ->                  -- model : TInterface "Gtk" "TreeModel"
    Ptr (Ptr TreePath) ->                   -- path : TInterface "Gtk" "TreePath"
    Ptr TreeIter ->                         -- iter : TInterface "Gtk" "TreeIter"
    IO CInt


iconViewGetTooltipContext ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- x
    Int32 ->                                -- y
    Bool ->                                 -- keyboard_tip
    m (Bool,Int32,Int32,TreeModel,TreePath,TreeIter)
iconViewGetTooltipContext _obj x y keyboard_tip = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    x' <- allocMem :: IO (Ptr Int32)
    poke x' x
    y' <- allocMem :: IO (Ptr Int32)
    poke y' y
    let keyboard_tip' = (fromIntegral . fromEnum) keyboard_tip
    model <- allocMem :: IO (Ptr (Ptr TreeModel))
    path <- allocMem :: IO (Ptr (Ptr TreePath))
    iter <- callocBoxedBytes 32 :: IO (Ptr TreeIter)
    result <- gtk_icon_view_get_tooltip_context _obj' x' y' keyboard_tip' model path iter
    let result' = (/= 0) result
    x'' <- peek x'
    y'' <- peek y'
    model' <- peek model
    model'' <- (newObject TreeModel) model'
    path' <- peek path
    path'' <- (wrapBoxed TreePath) path'
    iter' <- (wrapBoxed TreeIter) iter
    touchManagedPtr _obj
    freeMem x'
    freeMem y'
    freeMem model
    freeMem path
    return (result', x'', y'', model'', path'', iter')

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

foreign import ccall "gtk_icon_view_get_visible_range" gtk_icon_view_get_visible_range :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr (Ptr TreePath) ->                   -- start_path : TInterface "Gtk" "TreePath"
    Ptr (Ptr TreePath) ->                   -- end_path : TInterface "Gtk" "TreePath"
    IO CInt


iconViewGetVisibleRange ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m (Bool,TreePath,TreePath)
iconViewGetVisibleRange _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    start_path <- allocMem :: IO (Ptr (Ptr TreePath))
    end_path <- allocMem :: IO (Ptr (Ptr TreePath))
    result <- gtk_icon_view_get_visible_range _obj' start_path end_path
    let result' = (/= 0) result
    start_path' <- peek start_path
    start_path'' <- (wrapBoxed TreePath) start_path'
    end_path' <- peek end_path
    end_path'' <- (wrapBoxed TreePath) end_path'
    touchManagedPtr _obj
    freeMem start_path
    freeMem end_path
    return (result', start_path'', end_path'')

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

foreign import ccall "gtk_icon_view_item_activated" gtk_icon_view_item_activated :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    IO ()


iconViewItemActivated ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    m ()
iconViewItemActivated _obj path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    gtk_icon_view_item_activated _obj' path'
    touchManagedPtr _obj
    touchManagedPtr path
    return ()

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

foreign import ccall "gtk_icon_view_path_is_selected" gtk_icon_view_path_is_selected :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    IO CInt


iconViewPathIsSelected ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    m Bool
iconViewPathIsSelected _obj path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    result <- gtk_icon_view_path_is_selected _obj' path'
    let result' = (/= 0) result
    touchManagedPtr _obj
    touchManagedPtr path
    return result'

-- method IconView::scroll_to_path
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "use_align", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "row_align", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "col_align", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "use_align", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "row_align", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "col_align", argType = TBasicType TFloat, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_scroll_to_path" gtk_icon_view_scroll_to_path :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    CInt ->                                 -- use_align : TBasicType TBoolean
    CFloat ->                               -- row_align : TBasicType TFloat
    CFloat ->                               -- col_align : TBasicType TFloat
    IO ()


iconViewScrollToPath ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    Bool ->                                 -- use_align
    Float ->                                -- row_align
    Float ->                                -- col_align
    m ()
iconViewScrollToPath _obj path use_align row_align col_align = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    let use_align' = (fromIntegral . fromEnum) use_align
    let row_align' = realToFrac row_align
    let col_align' = realToFrac col_align
    gtk_icon_view_scroll_to_path _obj' path' use_align' row_align' col_align'
    touchManagedPtr _obj
    touchManagedPtr path
    return ()

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

foreign import ccall "gtk_icon_view_select_all" gtk_icon_view_select_all :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO ()


iconViewSelectAll ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m ()
iconViewSelectAll _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_select_all _obj'
    touchManagedPtr _obj
    return ()

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

foreign import ccall "gtk_icon_view_select_path" gtk_icon_view_select_path :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    IO ()


iconViewSelectPath ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    m ()
iconViewSelectPath _obj path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    gtk_icon_view_select_path _obj' path'
    touchManagedPtr _obj
    touchManagedPtr path
    return ()

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

foreign import ccall "gtk_icon_view_selected_foreach" gtk_icon_view_selected_foreach :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    FunPtr IconViewForeachFuncC ->          -- func : TInterface "Gtk" "IconViewForeachFunc"
    Ptr () ->                               -- data : TBasicType TVoid
    IO ()


iconViewSelectedForeach ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    IconViewForeachFunc ->                  -- func
    m ()
iconViewSelectedForeach _obj func = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    func' <- mkIconViewForeachFunc (iconViewForeachFuncWrapper Nothing func)
    let data_ = nullPtr
    gtk_icon_view_selected_foreach _obj' func' data_
    safeFreeFunPtr $ castFunPtrToPtr func'
    touchManagedPtr _obj
    return ()

-- method IconView::set_activate_on_single_click
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "single", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "single", 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_icon_view_set_activate_on_single_click" gtk_icon_view_set_activate_on_single_click :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    CInt ->                                 -- single : TBasicType TBoolean
    IO ()


iconViewSetActivateOnSingleClick ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- single
    m ()
iconViewSetActivateOnSingleClick _obj single = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let single' = (fromIntegral . fromEnum) single
    gtk_icon_view_set_activate_on_single_click _obj' single'
    touchManagedPtr _obj
    return ()

-- method IconView::set_column_spacing
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "column_spacing", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "column_spacing", 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_icon_view_set_column_spacing" gtk_icon_view_set_column_spacing :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- column_spacing : TBasicType TInt32
    IO ()


iconViewSetColumnSpacing ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- column_spacing
    m ()
iconViewSetColumnSpacing _obj column_spacing = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_column_spacing _obj' column_spacing
    touchManagedPtr _obj
    return ()

-- method IconView::set_columns
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "columns", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "columns", 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_icon_view_set_columns" gtk_icon_view_set_columns :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- columns : TBasicType TInt32
    IO ()


iconViewSetColumns ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- columns
    m ()
iconViewSetColumns _obj columns = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_columns _obj' columns
    touchManagedPtr _obj
    return ()

-- method IconView::set_cursor
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start_editing", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start_editing", 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_icon_view_set_cursor" gtk_icon_view_set_cursor :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    Ptr CellRenderer ->                     -- cell : TInterface "Gtk" "CellRenderer"
    CInt ->                                 -- start_editing : TBasicType TBoolean
    IO ()


iconViewSetCursor ::
    (MonadIO m, IconViewK a, CellRendererK b) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    Maybe (b) ->                            -- cell
    Bool ->                                 -- start_editing
    m ()
iconViewSetCursor _obj path cell start_editing = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    maybeCell <- case cell of
        Nothing -> return nullPtr
        Just jCell -> do
            let jCell' = unsafeManagedPtrCastPtr jCell
            return jCell'
    let start_editing' = (fromIntegral . fromEnum) start_editing
    gtk_icon_view_set_cursor _obj' path' maybeCell start_editing'
    touchManagedPtr _obj
    touchManagedPtr path
    whenJust cell touchManagedPtr
    return ()

-- method IconView::set_drag_dest_item
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pos", argType = TInterface "Gtk" "IconViewDropPosition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pos", argType = TInterface "Gtk" "IconViewDropPosition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_set_drag_dest_item" gtk_icon_view_set_drag_dest_item :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    CUInt ->                                -- pos : TInterface "Gtk" "IconViewDropPosition"
    IO ()


iconViewSetDragDestItem ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Maybe (TreePath) ->                     -- path
    IconViewDropPosition ->                 -- pos
    m ()
iconViewSetDragDestItem _obj path pos = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybePath <- case path of
        Nothing -> return nullPtr
        Just jPath -> do
            let jPath' = unsafeManagedPtrGetPtr jPath
            return jPath'
    let pos' = (fromIntegral . fromEnum) pos
    gtk_icon_view_set_drag_dest_item _obj' maybePath pos'
    touchManagedPtr _obj
    whenJust path touchManagedPtr
    return ()

-- method IconView::set_item_orientation
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_set_item_orientation" gtk_icon_view_set_item_orientation :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    CUInt ->                                -- orientation : TInterface "Gtk" "Orientation"
    IO ()


iconViewSetItemOrientation ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Orientation ->                          -- orientation
    m ()
iconViewSetItemOrientation _obj orientation = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let orientation' = (fromIntegral . fromEnum) orientation
    gtk_icon_view_set_item_orientation _obj' orientation'
    touchManagedPtr _obj
    return ()

-- method IconView::set_item_padding
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "item_padding", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "item_padding", 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_icon_view_set_item_padding" gtk_icon_view_set_item_padding :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- item_padding : TBasicType TInt32
    IO ()


iconViewSetItemPadding ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- item_padding
    m ()
iconViewSetItemPadding _obj item_padding = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_item_padding _obj' item_padding
    touchManagedPtr _obj
    return ()

-- method IconView::set_item_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "item_width", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "item_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_icon_view_set_item_width" gtk_icon_view_set_item_width :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- item_width : TBasicType TInt32
    IO ()


iconViewSetItemWidth ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- item_width
    m ()
iconViewSetItemWidth _obj item_width = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_item_width _obj' item_width
    touchManagedPtr _obj
    return ()

-- method IconView::set_margin
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "margin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "margin", 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_icon_view_set_margin" gtk_icon_view_set_margin :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- margin : TBasicType TInt32
    IO ()


iconViewSetMargin ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- margin
    m ()
iconViewSetMargin _obj margin = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_margin _obj' margin
    touchManagedPtr _obj
    return ()

-- method IconView::set_markup_column
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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" "IconView", 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_icon_view_set_markup_column" gtk_icon_view_set_markup_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- column : TBasicType TInt32
    IO ()


iconViewSetMarkupColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- column
    m ()
iconViewSetMarkupColumn _obj column = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_markup_column _obj' column
    touchManagedPtr _obj
    return ()

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

foreign import ccall "gtk_icon_view_set_model" gtk_icon_view_set_model :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreeModel ->                        -- model : TInterface "Gtk" "TreeModel"
    IO ()


iconViewSetModel ::
    (MonadIO m, IconViewK a, TreeModelK b) =>
    a ->                                    -- _obj
    Maybe (b) ->                            -- model
    m ()
iconViewSetModel _obj model = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    maybeModel <- case model of
        Nothing -> return nullPtr
        Just jModel -> do
            let jModel' = unsafeManagedPtrCastPtr jModel
            return jModel'
    gtk_icon_view_set_model _obj' maybeModel
    touchManagedPtr _obj
    whenJust model touchManagedPtr
    return ()

-- method IconView::set_pixbuf_column
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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" "IconView", 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_icon_view_set_pixbuf_column" gtk_icon_view_set_pixbuf_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- column : TBasicType TInt32
    IO ()


iconViewSetPixbufColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- column
    m ()
iconViewSetPixbufColumn _obj column = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_pixbuf_column _obj' column
    touchManagedPtr _obj
    return ()

-- method IconView::set_reorderable
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "reorderable", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "reorderable", 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_icon_view_set_reorderable" gtk_icon_view_set_reorderable :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    CInt ->                                 -- reorderable : TBasicType TBoolean
    IO ()


iconViewSetReorderable ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- reorderable
    m ()
iconViewSetReorderable _obj reorderable = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let reorderable' = (fromIntegral . fromEnum) reorderable
    gtk_icon_view_set_reorderable _obj' reorderable'
    touchManagedPtr _obj
    return ()

-- method IconView::set_row_spacing
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "row_spacing", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "row_spacing", 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_icon_view_set_row_spacing" gtk_icon_view_set_row_spacing :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- row_spacing : TBasicType TInt32
    IO ()


iconViewSetRowSpacing ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- row_spacing
    m ()
iconViewSetRowSpacing _obj row_spacing = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_row_spacing _obj' row_spacing
    touchManagedPtr _obj
    return ()

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

foreign import ccall "gtk_icon_view_set_selection_mode" gtk_icon_view_set_selection_mode :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    CUInt ->                                -- mode : TInterface "Gtk" "SelectionMode"
    IO ()


iconViewSetSelectionMode ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    SelectionMode ->                        -- mode
    m ()
iconViewSetSelectionMode _obj mode = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let mode' = (fromIntegral . fromEnum) mode
    gtk_icon_view_set_selection_mode _obj' mode'
    touchManagedPtr _obj
    return ()

-- method IconView::set_spacing
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "spacing", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "spacing", 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_icon_view_set_spacing" gtk_icon_view_set_spacing :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- spacing : TBasicType TInt32
    IO ()


iconViewSetSpacing ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- spacing
    m ()
iconViewSetSpacing _obj spacing = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_spacing _obj' spacing
    touchManagedPtr _obj
    return ()

-- method IconView::set_text_column
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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" "IconView", 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_icon_view_set_text_column" gtk_icon_view_set_text_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- column : TBasicType TInt32
    IO ()


iconViewSetTextColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- column
    m ()
iconViewSetTextColumn _obj column = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_text_column _obj' column
    touchManagedPtr _obj
    return ()

-- method IconView::set_tooltip_cell
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TInterface "Gtk" "Tooltip", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TInterface "Gtk" "Tooltip", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cell", argType = TInterface "Gtk" "CellRenderer", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_set_tooltip_cell" gtk_icon_view_set_tooltip_cell :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr Tooltip ->                          -- tooltip : TInterface "Gtk" "Tooltip"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    Ptr CellRenderer ->                     -- cell : TInterface "Gtk" "CellRenderer"
    IO ()


iconViewSetTooltipCell ::
    (MonadIO m, IconViewK a, TooltipK b, CellRendererK c) =>
    a ->                                    -- _obj
    b ->                                    -- tooltip
    TreePath ->                             -- path
    Maybe (c) ->                            -- cell
    m ()
iconViewSetTooltipCell _obj tooltip path cell = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let tooltip' = unsafeManagedPtrCastPtr tooltip
    let path' = unsafeManagedPtrGetPtr path
    maybeCell <- case cell of
        Nothing -> return nullPtr
        Just jCell -> do
            let jCell' = unsafeManagedPtrCastPtr jCell
            return jCell'
    gtk_icon_view_set_tooltip_cell _obj' tooltip' path' maybeCell
    touchManagedPtr _obj
    touchManagedPtr tooltip
    touchManagedPtr path
    whenJust cell touchManagedPtr
    return ()

-- method IconView::set_tooltip_column
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", 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" "IconView", 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_icon_view_set_tooltip_column" gtk_icon_view_set_tooltip_column :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Int32 ->                                -- column : TBasicType TInt32
    IO ()


iconViewSetTooltipColumn ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    Int32 ->                                -- column
    m ()
iconViewSetTooltipColumn _obj column = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_set_tooltip_column _obj' column
    touchManagedPtr _obj
    return ()

-- method IconView::set_tooltip_item
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TInterface "Gtk" "Tooltip", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "IconView", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tooltip", argType = TInterface "Gtk" "Tooltip", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "path", argType = TInterface "Gtk" "TreePath", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_icon_view_set_tooltip_item" gtk_icon_view_set_tooltip_item :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr Tooltip ->                          -- tooltip : TInterface "Gtk" "Tooltip"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    IO ()


iconViewSetTooltipItem ::
    (MonadIO m, IconViewK a, TooltipK b) =>
    a ->                                    -- _obj
    b ->                                    -- tooltip
    TreePath ->                             -- path
    m ()
iconViewSetTooltipItem _obj tooltip path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let tooltip' = unsafeManagedPtrCastPtr tooltip
    let path' = unsafeManagedPtrGetPtr path
    gtk_icon_view_set_tooltip_item _obj' tooltip' path'
    touchManagedPtr _obj
    touchManagedPtr tooltip
    touchManagedPtr path
    return ()

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

foreign import ccall "gtk_icon_view_unselect_all" gtk_icon_view_unselect_all :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO ()


iconViewUnselectAll ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m ()
iconViewUnselectAll _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_unselect_all _obj'
    touchManagedPtr _obj
    return ()

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

foreign import ccall "gtk_icon_view_unselect_path" gtk_icon_view_unselect_path :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    Ptr TreePath ->                         -- path : TInterface "Gtk" "TreePath"
    IO ()


iconViewUnselectPath ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    TreePath ->                             -- path
    m ()
iconViewUnselectPath _obj path = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let path' = unsafeManagedPtrGetPtr path
    gtk_icon_view_unselect_path _obj' path'
    touchManagedPtr _obj
    touchManagedPtr path
    return ()

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

foreign import ccall "gtk_icon_view_unset_model_drag_dest" gtk_icon_view_unset_model_drag_dest :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO ()


iconViewUnsetModelDragDest ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m ()
iconViewUnsetModelDragDest _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_unset_model_drag_dest _obj'
    touchManagedPtr _obj
    return ()

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

foreign import ccall "gtk_icon_view_unset_model_drag_source" gtk_icon_view_unset_model_drag_source :: 
    Ptr IconView ->                         -- _obj : TInterface "Gtk" "IconView"
    IO ()


iconViewUnsetModelDragSource ::
    (MonadIO m, IconViewK a) =>
    a ->                                    -- _obj
    m ()
iconViewUnsetModelDragSource _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_icon_view_unset_model_drag_source _obj'
    touchManagedPtr _obj
    return ()