module Graphics.UI.Gtk.MenuComboToolbar.ToolButton (
  ToolButton,
  ToolButtonClass,
  castToToolButton, gTypeToolButton,
  toToolButton,
  toolButtonNew,
  toolButtonNewFromStock,
  toolButtonSetLabel,
  toolButtonGetLabel,
  toolButtonSetUseUnderline,
  toolButtonGetUseUnderline,
  toolButtonSetStockId,
  toolButtonGetStockId,
  toolButtonSetIconWidget,
  toolButtonGetIconWidget,
  toolButtonSetLabelWidget,
  toolButtonGetLabelWidget,
  toolButtonSetIconName,
  toolButtonGetIconName,
  toolButtonLabel,
  toolButtonUseUnderline,
  toolButtonLabelWidget,
  toolButtonStockId,
  toolButtonIconName,
  toolButtonIconWidget,
  onToolButtonClicked,
  afterToolButtonClicked,
  ) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
import Graphics.UI.Gtk.General.StockItems
toolButtonNew :: (WidgetClass iconWidget, GlibString string) =>
    Maybe iconWidget 
                     
 -> Maybe string 
                     
 -> IO ToolButton
toolButtonNew iconWidget label =
  makeNewObject mkToolButton $
  liftM (castPtr :: Ptr ToolItem -> Ptr ToolButton) $
  maybeWith withUTFString label $ \labelPtr ->
  (\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_new argPtr1 arg2)
    (maybe (Widget nullForeignPtr) toWidget iconWidget)
    labelPtr
toolButtonNewFromStock ::
    StockId 
 -> IO ToolButton
toolButtonNewFromStock stockId =
  makeNewObject mkToolButton $
  liftM (castPtr :: Ptr ToolItem -> Ptr ToolButton) $
  withUTFString stockId $ \stockIdPtr ->
  gtk_tool_button_new_from_stock
    stockIdPtr
toolButtonSetLabel :: (ToolButtonClass self, GlibString string) => self
 -> Maybe string 
                 
 -> IO ()
toolButtonSetLabel self label =
  maybeWith withUTFString label $ \labelPtr ->
  (\(ToolButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_set_label argPtr1 arg2)
    (toToolButton self)
    labelPtr
toolButtonGetLabel :: (ToolButtonClass self, GlibString string) => self -> IO (Maybe string)
toolButtonGetLabel self =
  (\(ToolButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_get_label argPtr1)
    (toToolButton self)
  >>= maybePeek peekUTFString
toolButtonSetUseUnderline :: ToolButtonClass self => self -> Bool -> IO ()
toolButtonSetUseUnderline self useUnderline =
  (\(ToolButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_set_use_underline argPtr1 arg2)
    (toToolButton self)
    (fromBool useUnderline)
toolButtonGetUseUnderline :: ToolButtonClass self => self -> IO Bool
toolButtonGetUseUnderline self =
  liftM toBool $
  (\(ToolButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_get_use_underline argPtr1)
    (toToolButton self)
toolButtonSetStockId :: ToolButtonClass self => self
 -> Maybe StockId 
 -> IO ()
toolButtonSetStockId self stockId =
  maybeWith withUTFString stockId $ \stockIdPtr ->
  (\(ToolButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_set_stock_id argPtr1 arg2)
    (toToolButton self)
    stockIdPtr
toolButtonGetStockId :: ToolButtonClass self => self -> IO (Maybe StockId)
toolButtonGetStockId self =
  (\(ToolButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_get_stock_id argPtr1)
    (toToolButton self)
  >>= maybePeek peekUTFString
toolButtonSetIconWidget :: (ToolButtonClass self, WidgetClass iconWidget) => self
 -> Maybe iconWidget 
 -> IO ()
toolButtonSetIconWidget self iconWidget =
  (\(ToolButton arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_tool_button_set_icon_widget argPtr1 argPtr2)
    (toToolButton self)
    (maybe (Widget nullForeignPtr) toWidget iconWidget)
toolButtonGetIconWidget :: ToolButtonClass self => self
 -> IO (Maybe Widget) 
                      
toolButtonGetIconWidget self =
  maybeNull (makeNewObject mkWidget) $
  (\(ToolButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_get_icon_widget argPtr1)
    (toToolButton self)
toolButtonSetLabelWidget :: (ToolButtonClass self, WidgetClass labelWidget) => self
 -> Maybe labelWidget 
                      
 -> IO ()
toolButtonSetLabelWidget self labelWidget =
  (\(ToolButton arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_tool_button_set_label_widget argPtr1 argPtr2)
    (toToolButton self)
    (maybe (Widget nullForeignPtr) toWidget labelWidget)
toolButtonGetLabelWidget :: ToolButtonClass self => self
 -> IO (Maybe Widget) 
                      
toolButtonGetLabelWidget self =
  maybeNull (makeNewObject mkWidget) $
  (\(ToolButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_get_label_widget argPtr1)
    (toToolButton self)
toolButtonSetIconName :: (ToolButtonClass self, GlibString string) => self
 -> string 
 -> IO ()
toolButtonSetIconName self iconName =
  withUTFString iconName $ \iconNamePtr ->
  (\(ToolButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_set_icon_name argPtr1 arg2)
    (toToolButton self)
    iconNamePtr
toolButtonGetIconName :: (ToolButtonClass self, GlibString string) => self
 -> IO string 
              
toolButtonGetIconName self =
  (\(ToolButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_button_get_icon_name argPtr1)
    (toToolButton self)
  >>= \strPtr -> if strPtr == nullPtr
                then return ""
                else peekUTFString strPtr
toolButtonLabel :: (ToolButtonClass self, GlibString string) => Attr self (Maybe string)
toolButtonLabel = newAttr
  toolButtonGetLabel
  toolButtonSetLabel
toolButtonUseUnderline :: ToolButtonClass self => Attr self Bool
toolButtonUseUnderline = newAttr
  toolButtonGetUseUnderline
  toolButtonSetUseUnderline
toolButtonLabelWidget :: (ToolButtonClass self, WidgetClass labelWidget) => ReadWriteAttr self (Maybe Widget) (Maybe labelWidget)
toolButtonLabelWidget = newAttr
  toolButtonGetLabelWidget
  toolButtonSetLabelWidget
toolButtonStockId :: ToolButtonClass self => ReadWriteAttr self (Maybe StockId) (Maybe StockId)
toolButtonStockId = newAttr
  toolButtonGetStockId
  toolButtonSetStockId
toolButtonIconName :: (ToolButtonClass self, GlibString string) => Attr self string
toolButtonIconName = newAttr
  toolButtonGetIconName
  toolButtonSetIconName
toolButtonIconWidget :: (ToolButtonClass self, WidgetClass iconWidget) => ReadWriteAttr self (Maybe Widget) (Maybe iconWidget)
toolButtonIconWidget = newAttr
  toolButtonGetIconWidget
  toolButtonSetIconWidget
onToolButtonClicked, afterToolButtonClicked :: ToolButtonClass self => self
 -> IO ()
 -> IO (ConnectId self)
onToolButtonClicked = connect_NONE__NONE "clicked" False
afterToolButtonClicked = connect_NONE__NONE "clicked" True
foreign import ccall safe "gtk_tool_button_new"
  gtk_tool_button_new :: ((Ptr Widget) -> ((Ptr CChar) -> (IO (Ptr ToolItem))))
foreign import ccall safe "gtk_tool_button_new_from_stock"
  gtk_tool_button_new_from_stock :: ((Ptr CChar) -> (IO (Ptr ToolItem)))
foreign import ccall safe "gtk_tool_button_set_label"
  gtk_tool_button_set_label :: ((Ptr ToolButton) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_tool_button_get_label"
  gtk_tool_button_get_label :: ((Ptr ToolButton) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_tool_button_set_use_underline"
  gtk_tool_button_set_use_underline :: ((Ptr ToolButton) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_tool_button_get_use_underline"
  gtk_tool_button_get_use_underline :: ((Ptr ToolButton) -> (IO CInt))
foreign import ccall safe "gtk_tool_button_set_stock_id"
  gtk_tool_button_set_stock_id :: ((Ptr ToolButton) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_tool_button_get_stock_id"
  gtk_tool_button_get_stock_id :: ((Ptr ToolButton) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_tool_button_set_icon_widget"
  gtk_tool_button_set_icon_widget :: ((Ptr ToolButton) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_tool_button_get_icon_widget"
  gtk_tool_button_get_icon_widget :: ((Ptr ToolButton) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_tool_button_set_label_widget"
  gtk_tool_button_set_label_widget :: ((Ptr ToolButton) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_tool_button_get_label_widget"
  gtk_tool_button_get_label_widget :: ((Ptr ToolButton) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_tool_button_set_icon_name"
  gtk_tool_button_set_icon_name :: ((Ptr ToolButton) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_tool_button_get_icon_name"
  gtk_tool_button_get_icon_name :: ((Ptr ToolButton) -> (IO (Ptr CChar)))