{-# LINE 2 "./Graphics/UI/Gtk/ModelView/CellRendererPixbuf.chs" #-}
module Graphics.UI.Gtk.ModelView.CellRendererPixbuf (
  CellRendererPixbuf,
  CellRendererPixbufClass,
  castToCellRendererPixbuf, gTypeCellRendererPixbuf,
  toCellRendererPixbuf,
  cellRendererPixbufNew,
  cellPixbuf,
  cellPixbufExpanderOpen,
  cellPixbufExpanderClosed,
  cellPixbufStockId,
  cellPixbufStockSize,
  cellPixbufStockDetail,
  cellPixbufIconName,
  cellPixbufFollowState,
  ) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes (Attr)
import System.Glib.Properties
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
{-# LINE 83 "./Graphics/UI/Gtk/ModelView/CellRendererPixbuf.chs" #-}
{-# LINE 85 "./Graphics/UI/Gtk/ModelView/CellRendererPixbuf.chs" #-}
cellRendererPixbufNew :: IO CellRendererPixbuf
cellRendererPixbufNew =
  makeNewObject mkCellRendererPixbuf $
  liftM (castPtr :: Ptr CellRenderer -> Ptr CellRendererPixbuf) $
  gtk_cell_renderer_pixbuf_new
{-# LINE 96 "./Graphics/UI/Gtk/ModelView/CellRendererPixbuf.chs" #-}
cellPixbuf :: CellRendererPixbufClass self => Attr self Pixbuf
cellPixbuf = newAttrFromObjectProperty "pixbuf"
  gdk_pixbuf_get_type
{-# LINE 105 "./Graphics/UI/Gtk/ModelView/CellRendererPixbuf.chs" #-}
cellPixbufExpanderOpen :: CellRendererPixbufClass self => Attr self Pixbuf
cellPixbufExpanderOpen = newAttrFromObjectProperty "pixbuf-expander-open"
  gdk_pixbuf_get_type
{-# LINE 111 "./Graphics/UI/Gtk/ModelView/CellRendererPixbuf.chs" #-}
cellPixbufExpanderClosed :: CellRendererPixbufClass self => Attr self Pixbuf
cellPixbufExpanderClosed = newAttrFromObjectProperty "pixbuf-expander-closed"
  gdk_pixbuf_get_type
{-# LINE 117 "./Graphics/UI/Gtk/ModelView/CellRendererPixbuf.chs" #-}
cellPixbufStockId :: (CellRendererPixbufClass self, GlibString string) => Attr self string
cellPixbufStockId = newAttrFromStringProperty "stock-id"
cellPixbufStockSize :: CellRendererPixbufClass self => Attr self Int
cellPixbufStockSize = newAttrFromUIntProperty "stock-size"
cellPixbufStockDetail :: (CellRendererPixbufClass self, GlibString string) => Attr self string
cellPixbufStockDetail = newAttrFromStringProperty "stock-detail"
cellPixbufIconName :: (CellRendererPixbufClass self, GlibString string) => Attr self string
cellPixbufIconName = newAttrFromStringProperty "icon-name"
cellPixbufFollowState :: CellRendererPixbufClass self => Attr self Bool
cellPixbufFollowState = newAttrFromBoolProperty "follow-state"
foreign import ccall unsafe "gtk_cell_renderer_pixbuf_new"
  gtk_cell_renderer_pixbuf_new :: (IO (Ptr CellRenderer))
foreign import ccall unsafe "gdk_pixbuf_get_type"
  gdk_pixbuf_get_type :: CULong