module Graphics.UI.Gtk.MenuComboToolbar.ToolItem (
  ToolItem,
  ToolItemClass,
  castToToolItem, gTypeToolItem,
  toToolItem,
  toolItemNew,
  toolItemSetHomogeneous,
  toolItemGetHomogeneous,
  toolItemSetExpand,
  toolItemGetExpand,
  toolItemSetUseDragWindow,
  toolItemGetUseDragWindow,
  toolItemSetVisibleHorizontal,
  toolItemGetVisibleHorizontal,
  toolItemSetVisibleVertical,
  toolItemGetVisibleVertical,
  toolItemSetIsImportant,
  toolItemGetIsImportant,
  IconSize,
  toolItemGetIconSize,
  Orientation(..),
  toolItemGetOrientation,
  ToolbarStyle(..),
  toolItemGetToolbarStyle,
  ReliefStyle(..),
  toolItemGetReliefStyle,
  toolItemRetrieveProxyMenuItem,
  toolItemGetProxyMenuItem,
  toolItemSetProxyMenuItem,
  toolItemGetEllipsizeMode,
  toolItemGetTextAlignment,
  toolItemGetTextOrientation,
  toolItemGetTextSizeGroup,
  toolItemVisibleHorizontal,
  toolItemVisibleVertical,
  toolItemIsImportant,
  toolItemExpand,
  toolItemHomogeneous,
  toolItemUseDragWindow,
  ) 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.Rendering.Pango.Enums (EllipsizeMode (..))
import Graphics.UI.Gtk.Misc.SizeGroup
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.General.Structs (IconSize)
import Graphics.UI.Gtk.General.Enums (Orientation(..), ToolbarStyle(..), ReliefStyle(..))
toolItemNew :: IO ToolItem
toolItemNew =
  makeNewObject mkToolItem $
  gtk_tool_item_new
toolItemSetHomogeneous :: ToolItemClass self => self
 -> Bool 
          
 -> IO ()
toolItemSetHomogeneous self homogeneous =
  (\(ToolItem arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_set_homogeneous argPtr1 arg2)
    (toToolItem self)
    (fromBool homogeneous)
toolItemGetHomogeneous :: ToolItemClass self => self -> IO Bool
toolItemGetHomogeneous self =
  liftM toBool $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_homogeneous argPtr1)
    (toToolItem self)
toolItemSetExpand :: ToolItemClass self => self -> Bool -> IO ()
toolItemSetExpand self expand =
  (\(ToolItem arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_set_expand argPtr1 arg2)
    (toToolItem self)
    (fromBool expand)
toolItemGetExpand :: ToolItemClass self => self -> IO Bool
toolItemGetExpand self =
  liftM toBool $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_expand argPtr1)
    (toToolItem self)
toolItemSetUseDragWindow :: ToolItemClass self => self -> Bool -> IO ()
toolItemSetUseDragWindow self useDragWindow =
  (\(ToolItem arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_set_use_drag_window argPtr1 arg2)
    (toToolItem self)
    (fromBool useDragWindow)
toolItemGetUseDragWindow :: ToolItemClass self => self -> IO Bool
toolItemGetUseDragWindow self =
  liftM toBool $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_use_drag_window argPtr1)
    (toToolItem self)
toolItemSetVisibleHorizontal :: ToolItemClass self => self -> Bool -> IO ()
toolItemSetVisibleHorizontal self visibleHorizontal =
  (\(ToolItem arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_set_visible_horizontal argPtr1 arg2)
    (toToolItem self)
    (fromBool visibleHorizontal)
toolItemGetVisibleHorizontal :: ToolItemClass self => self -> IO Bool
toolItemGetVisibleHorizontal self =
  liftM toBool $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_visible_horizontal argPtr1)
    (toToolItem self)
toolItemSetVisibleVertical :: ToolItemClass self => self -> Bool -> IO ()
toolItemSetVisibleVertical self visibleVertical =
  (\(ToolItem arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_set_visible_vertical argPtr1 arg2)
    (toToolItem self)
    (fromBool visibleVertical)
toolItemGetVisibleVertical :: ToolItemClass self => self -> IO Bool
toolItemGetVisibleVertical self =
  liftM toBool $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_visible_vertical argPtr1)
    (toToolItem self)
toolItemSetIsImportant :: ToolItemClass self => self -> Bool -> IO ()
toolItemSetIsImportant self isImportant =
  (\(ToolItem arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_set_is_important argPtr1 arg2)
    (toToolItem self)
    (fromBool isImportant)
toolItemGetIsImportant :: ToolItemClass self => self -> IO Bool
toolItemGetIsImportant self =
  liftM toBool $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_is_important argPtr1)
    (toToolItem self)
toolItemGetIconSize :: ToolItemClass self => self -> IO IconSize
toolItemGetIconSize self =
  liftM (toEnum . fromIntegral) $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_icon_size argPtr1)
    (toToolItem self)
toolItemGetOrientation :: ToolItemClass self => self -> IO Orientation
toolItemGetOrientation self =
  liftM (toEnum . fromIntegral) $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_orientation argPtr1)
    (toToolItem self)
toolItemGetToolbarStyle :: ToolItemClass self => self -> IO ToolbarStyle
toolItemGetToolbarStyle self =
  liftM (toEnum . fromIntegral) $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_toolbar_style argPtr1)
    (toToolItem self)
toolItemGetReliefStyle :: ToolItemClass self => self -> IO ReliefStyle
toolItemGetReliefStyle self =
  liftM (toEnum . fromIntegral) $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_relief_style argPtr1)
    (toToolItem self)
toolItemRetrieveProxyMenuItem :: ToolItemClass self => self -> IO (Maybe Widget)
toolItemRetrieveProxyMenuItem self =
  maybeNull (makeNewObject mkWidget) $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_retrieve_proxy_menu_item argPtr1)
    (toToolItem self)
toolItemGetProxyMenuItem :: (ToolItemClass self, GlibString string) => self
 -> string 
                      
 -> IO (Maybe Widget) 
                      
                      
toolItemGetProxyMenuItem self menuItemId =
  maybeNull (makeNewObject mkWidget) $
  withUTFString menuItemId $ \menuItemIdPtr ->
  (\(ToolItem arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_proxy_menu_item argPtr1 arg2)
    (toToolItem self)
    menuItemIdPtr
toolItemSetProxyMenuItem :: (ToolItemClass self, MenuItemClass menuItem, GlibString string) => self
 -> string 
 -> menuItem 
 -> IO ()
toolItemSetProxyMenuItem self menuItemId menuItem =
  withUTFString menuItemId $ \menuItemIdPtr ->
  (\(ToolItem arg1) arg2 (Widget arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg3 $ \argPtr3 ->gtk_tool_item_set_proxy_menu_item argPtr1 arg2 argPtr3)
    (toToolItem self)
    menuItemIdPtr
    (toWidget menuItem)
toolItemGetEllipsizeMode :: ToolItemClass item => item
                         -> IO EllipsizeMode 
toolItemGetEllipsizeMode item =
  liftM (toEnum . fromIntegral) $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_ellipsize_mode argPtr1)
    (toToolItem item)
toolItemGetTextAlignment :: ToolItemClass item => item
                         -> IO Double 
toolItemGetTextAlignment item =
  liftM realToFrac $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_text_alignment argPtr1)
     (toToolItem item)
toolItemGetTextOrientation :: ToolItemClass item => item
                           -> IO Orientation 
toolItemGetTextOrientation item =
  liftM (toEnum . fromIntegral) $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_text_orientation argPtr1)
     (toToolItem item)
toolItemGetTextSizeGroup :: ToolItemClass item => item
                         -> IO SizeGroup
toolItemGetTextSizeGroup item =
  makeNewGObject mkSizeGroup $
  (\(ToolItem arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tool_item_get_text_size_group argPtr1)
     (toToolItem item)
toolItemVisibleHorizontal :: ToolItemClass self => Attr self Bool
toolItemVisibleHorizontal = newAttr
  toolItemGetVisibleHorizontal
  toolItemSetVisibleHorizontal
toolItemVisibleVertical :: ToolItemClass self => Attr self Bool
toolItemVisibleVertical = newAttr
  toolItemGetVisibleVertical
  toolItemSetVisibleVertical
toolItemIsImportant :: ToolItemClass self => Attr self Bool
toolItemIsImportant = newAttr
  toolItemGetIsImportant
  toolItemSetIsImportant
toolItemExpand :: ToolItemClass self => Attr self Bool
toolItemExpand = newAttr
  toolItemGetExpand
  toolItemSetExpand
toolItemHomogeneous :: ToolItemClass self => Attr self Bool
toolItemHomogeneous = newAttr
  toolItemGetHomogeneous
  toolItemSetHomogeneous
toolItemUseDragWindow :: ToolItemClass self => Attr self Bool
toolItemUseDragWindow = newAttr
  toolItemGetUseDragWindow
  toolItemSetUseDragWindow
foreign import ccall unsafe "gtk_tool_item_new"
  gtk_tool_item_new :: (IO (Ptr ToolItem))
foreign import ccall safe "gtk_tool_item_set_homogeneous"
  gtk_tool_item_set_homogeneous :: ((Ptr ToolItem) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_tool_item_get_homogeneous"
  gtk_tool_item_get_homogeneous :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall safe "gtk_tool_item_set_expand"
  gtk_tool_item_set_expand :: ((Ptr ToolItem) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_tool_item_get_expand"
  gtk_tool_item_get_expand :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall safe "gtk_tool_item_set_use_drag_window"
  gtk_tool_item_set_use_drag_window :: ((Ptr ToolItem) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_tool_item_get_use_drag_window"
  gtk_tool_item_get_use_drag_window :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall safe "gtk_tool_item_set_visible_horizontal"
  gtk_tool_item_set_visible_horizontal :: ((Ptr ToolItem) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_tool_item_get_visible_horizontal"
  gtk_tool_item_get_visible_horizontal :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall safe "gtk_tool_item_set_visible_vertical"
  gtk_tool_item_set_visible_vertical :: ((Ptr ToolItem) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_tool_item_get_visible_vertical"
  gtk_tool_item_get_visible_vertical :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall safe "gtk_tool_item_set_is_important"
  gtk_tool_item_set_is_important :: ((Ptr ToolItem) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_tool_item_get_is_important"
  gtk_tool_item_get_is_important :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall unsafe "gtk_tool_item_get_icon_size"
  gtk_tool_item_get_icon_size :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall unsafe "gtk_tool_item_get_orientation"
  gtk_tool_item_get_orientation :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall unsafe "gtk_tool_item_get_toolbar_style"
  gtk_tool_item_get_toolbar_style :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall unsafe "gtk_tool_item_get_relief_style"
  gtk_tool_item_get_relief_style :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall unsafe "gtk_tool_item_retrieve_proxy_menu_item"
  gtk_tool_item_retrieve_proxy_menu_item :: ((Ptr ToolItem) -> (IO (Ptr Widget)))
foreign import ccall unsafe "gtk_tool_item_get_proxy_menu_item"
  gtk_tool_item_get_proxy_menu_item :: ((Ptr ToolItem) -> ((Ptr CChar) -> (IO (Ptr Widget))))
foreign import ccall safe "gtk_tool_item_set_proxy_menu_item"
  gtk_tool_item_set_proxy_menu_item :: ((Ptr ToolItem) -> ((Ptr CChar) -> ((Ptr Widget) -> (IO ()))))
foreign import ccall safe "gtk_tool_item_get_ellipsize_mode"
  gtk_tool_item_get_ellipsize_mode :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall safe "gtk_tool_item_get_text_alignment"
  gtk_tool_item_get_text_alignment :: ((Ptr ToolItem) -> (IO CFloat))
foreign import ccall safe "gtk_tool_item_get_text_orientation"
  gtk_tool_item_get_text_orientation :: ((Ptr ToolItem) -> (IO CInt))
foreign import ccall safe "gtk_tool_item_get_text_size_group"
  gtk_tool_item_get_text_size_group :: ((Ptr ToolItem) -> (IO (Ptr SizeGroup)))