module Graphics.UI.Gtk.Buttons.Button (
  Button,
  ButtonClass,
  castToButton, gTypeButton,
  toButton,
  buttonNew,
  buttonNewWithLabel,
  buttonNewWithMnemonic,
  buttonNewFromStock,
  buttonPressed,
  buttonReleased,
  buttonClicked,
  buttonEnter,
  buttonLeave,
  ReliefStyle(..),
  buttonSetRelief,
  buttonGetRelief,
  buttonSetLabel,
  buttonGetLabel,
  buttonSetUseStock,
  buttonGetUseStock,
  buttonSetUseUnderline,
  buttonGetUseUnderline,
  buttonSetFocusOnClick,
  buttonGetFocusOnClick,
  buttonSetAlignment,
  buttonGetAlignment,
  buttonGetImage,
  buttonSetImage,
  PositionType(..),
  buttonSetImagePosition,
  buttonGetImagePosition,
  buttonGetEventWindow,
  buttonLabel,
  buttonUseUnderline,
  buttonUseStock,
  buttonFocusOnClick,
  buttonRelief,
  buttonXalign,
  buttonYalign,
  buttonImage,
  buttonImagePosition,
  buttonActivated,
  ) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import System.Glib.Properties
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
import Graphics.UI.Gtk.General.Enums (ReliefStyle(..), PositionType(..))
import Graphics.UI.Gtk.General.StockItems
buttonNew :: IO Button
buttonNew =
  makeNewObject mkButton $
  liftM (castPtr :: Ptr Widget -> Ptr Button) $
  gtk_button_new
buttonNewWithLabel :: GlibString string
 => string 
 -> IO Button
buttonNewWithLabel label =
  makeNewObject mkButton $
  liftM (castPtr :: Ptr Widget -> Ptr Button) $
  withUTFString label $ \labelPtr ->
  gtk_button_new_with_label
    labelPtr
buttonNewWithMnemonic :: GlibString string
 => string 
              
 -> IO Button
buttonNewWithMnemonic label =
  makeNewObject mkButton $
  liftM (castPtr :: Ptr Widget -> Ptr Button) $
  withUTFString label $ \labelPtr ->
  gtk_button_new_with_mnemonic
    labelPtr
buttonNewFromStock ::
    StockId 
 -> IO Button
buttonNewFromStock stockId =
  makeNewObject mkButton $
  liftM (castPtr :: Ptr Widget -> Ptr Button) $
  withUTFString stockId $ \stockIdPtr ->
  throwIfNull "buttonNewFromStock: Invalid stock identifier." $
  gtk_button_new_from_stock
    stockIdPtr
buttonPressed :: ButtonClass self => self -> IO ()
buttonPressed self =
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_pressed argPtr1)
    (toButton self)
buttonReleased :: ButtonClass self => self -> IO ()
buttonReleased self =
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_released argPtr1)
    (toButton self)
buttonClicked :: ButtonClass self => self -> IO ()
buttonClicked self =
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_clicked argPtr1)
    (toButton self)
buttonEnter :: ButtonClass self => self -> IO ()
buttonEnter self =
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_enter argPtr1)
    (toButton self)
buttonLeave :: ButtonClass self => self -> IO ()
buttonLeave self =
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_leave argPtr1)
    (toButton self)
buttonSetRelief :: ButtonClass self => self
 -> ReliefStyle 
 -> IO ()
buttonSetRelief self newstyle =
  (\(Button arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_set_relief argPtr1 arg2)
    (toButton self)
    ((fromIntegral . fromEnum) newstyle)
buttonGetRelief :: ButtonClass self => self
 -> IO ReliefStyle 
buttonGetRelief self =
  liftM (toEnum . fromIntegral) $
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_relief argPtr1)
    (toButton self)
buttonSetLabel :: (ButtonClass self, GlibString string) => self -> string -> IO ()
buttonSetLabel self label =
  withUTFString label $ \labelPtr ->
  (\(Button arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_set_label argPtr1 arg2)
    (toButton self)
    labelPtr
buttonGetLabel :: (ButtonClass self, GlibString string) => self -> IO string
buttonGetLabel self = do
  strPtr <- (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_label argPtr1)
    (toButton self)
  if strPtr==nullPtr then return "" else peekUTFString strPtr
buttonSetUseStock :: ButtonClass self => self
 -> Bool 
 -> IO ()
buttonSetUseStock self useStock =
  (\(Button arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_set_use_stock argPtr1 arg2)
    (toButton self)
    (fromBool useStock)
buttonGetUseStock :: ButtonClass self => self
 -> IO Bool 
            
buttonGetUseStock self =
  liftM toBool $
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_use_stock argPtr1)
    (toButton self)
buttonSetUseUnderline :: ButtonClass self => self
 -> Bool 
          
 -> IO ()
buttonSetUseUnderline self useUnderline =
  (\(Button arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_set_use_underline argPtr1 arg2)
    (toButton self)
    (fromBool useUnderline)
buttonGetUseUnderline :: ButtonClass self => self
 -> IO Bool 
            
buttonGetUseUnderline self =
  liftM toBool $
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_use_underline argPtr1)
    (toButton self)
buttonSetFocusOnClick :: ButtonClass self => self
 -> Bool 
          
 -> IO ()
buttonSetFocusOnClick self focusOnClick =
  (\(Button arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_set_focus_on_click argPtr1 arg2)
    (toButton self)
    (fromBool focusOnClick)
buttonGetFocusOnClick :: ButtonClass self => self
 -> IO Bool 
            
buttonGetFocusOnClick self =
  liftM toBool $
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_focus_on_click argPtr1)
    (toButton self)
buttonSetAlignment :: ButtonClass self => self
 -> (Float, Float) 
                   
                   
                   
 -> IO ()
buttonSetAlignment self (xalign, yalign) =
  (\(Button arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_set_alignment argPtr1 arg2 arg3)
    (toButton self)
    (realToFrac xalign)
    (realToFrac yalign)
buttonGetAlignment :: ButtonClass self => self
 -> IO (Float, Float) 
                      
buttonGetAlignment self =
  alloca $ \xalignPtr ->
  alloca $ \yalignPtr -> do
  (\(Button arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_alignment argPtr1 arg2 arg3)
    (toButton self)
    xalignPtr
    yalignPtr
  xalign <- peek xalignPtr
  yalign <- peek yalignPtr
  return (realToFrac xalign, realToFrac yalign)
buttonGetImage :: ButtonClass self => self
 -> IO (Maybe Widget) 
buttonGetImage self =
  maybeNull (makeNewObject mkWidget) $
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_image argPtr1)
    (toButton self)
buttonSetImage :: (ButtonClass self, WidgetClass image) => self
 -> image 
 -> IO ()
buttonSetImage self image =
  (\(Button arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_button_set_image argPtr1 argPtr2)
    (toButton self)
    (toWidget image)
buttonSetImagePosition :: ButtonClass self => self
 -> PositionType 
 -> IO ()
buttonSetImagePosition self position =
  (\(Button arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_set_image_position argPtr1 arg2)
    (toButton self)
    ((fromIntegral . fromEnum) position)
buttonGetImagePosition :: ButtonClass self => self
 -> IO PositionType 
buttonGetImagePosition self =
  liftM (toEnum . fromIntegral) $
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_image_position argPtr1)
    (toButton self)
buttonGetEventWindow :: ButtonClass self => self
                       -> IO (Maybe DrawWindow) 
buttonGetEventWindow self =
  maybeNull (makeNewGObject mkDrawWindow) $
  (\(Button arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_button_get_event_window argPtr1)
    (toButton self)
buttonLabel :: (ButtonClass self, GlibString string) => Attr self string
buttonLabel = newAttr
  buttonGetLabel
  buttonSetLabel
buttonUseUnderline :: ButtonClass self => Attr self Bool
buttonUseUnderline = newAttr
  buttonGetUseUnderline
  buttonSetUseUnderline
buttonUseStock :: ButtonClass self => Attr self Bool
buttonUseStock = newAttr
  buttonGetUseStock
  buttonSetUseStock
buttonFocusOnClick :: ButtonClass self => Attr self Bool
buttonFocusOnClick = newAttr
  buttonGetFocusOnClick
  buttonSetFocusOnClick
buttonRelief :: ButtonClass self => Attr self ReliefStyle
buttonRelief = newAttr
  buttonGetRelief
  buttonSetRelief
buttonXalign :: ButtonClass self => Attr self Float
buttonXalign = newAttrFromFloatProperty "xalign"
buttonYalign :: ButtonClass self => Attr self Float
buttonYalign = newAttrFromFloatProperty "yalign"
buttonImage :: (ButtonClass self, WidgetClass image) => ReadWriteAttr self (Maybe Widget) image
buttonImage = newAttr
  buttonGetImage
  buttonSetImage
buttonImagePosition :: ButtonClass self => Attr self PositionType
buttonImagePosition = newAttrFromEnumProperty "image-position"
                        gtk_position_type_get_type
buttonActivated :: ButtonClass self => Signal self (IO ())
buttonActivated = Signal (connect_NONE__NONE "clicked")
foreign import ccall unsafe "gtk_button_new"
  gtk_button_new :: (IO (Ptr Widget))
foreign import ccall unsafe "gtk_button_new_with_label"
  gtk_button_new_with_label :: ((Ptr CChar) -> (IO (Ptr Widget)))
foreign import ccall unsafe "gtk_button_new_with_mnemonic"
  gtk_button_new_with_mnemonic :: ((Ptr CChar) -> (IO (Ptr Widget)))
foreign import ccall unsafe "gtk_button_new_from_stock"
  gtk_button_new_from_stock :: ((Ptr CChar) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_button_pressed"
  gtk_button_pressed :: ((Ptr Button) -> (IO ()))
foreign import ccall safe "gtk_button_released"
  gtk_button_released :: ((Ptr Button) -> (IO ()))
foreign import ccall safe "gtk_button_clicked"
  gtk_button_clicked :: ((Ptr Button) -> (IO ()))
foreign import ccall safe "gtk_button_enter"
  gtk_button_enter :: ((Ptr Button) -> (IO ()))
foreign import ccall safe "gtk_button_leave"
  gtk_button_leave :: ((Ptr Button) -> (IO ()))
foreign import ccall safe "gtk_button_set_relief"
  gtk_button_set_relief :: ((Ptr Button) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_button_get_relief"
  gtk_button_get_relief :: ((Ptr Button) -> (IO CInt))
foreign import ccall safe "gtk_button_set_label"
  gtk_button_set_label :: ((Ptr Button) -> ((Ptr CChar) -> (IO ())))
foreign import ccall unsafe "gtk_button_get_label"
  gtk_button_get_label :: ((Ptr Button) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_button_set_use_stock"
  gtk_button_set_use_stock :: ((Ptr Button) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_button_get_use_stock"
  gtk_button_get_use_stock :: ((Ptr Button) -> (IO CInt))
foreign import ccall safe "gtk_button_set_use_underline"
  gtk_button_set_use_underline :: ((Ptr Button) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_button_get_use_underline"
  gtk_button_get_use_underline :: ((Ptr Button) -> (IO CInt))
foreign import ccall unsafe "gtk_button_set_focus_on_click"
  gtk_button_set_focus_on_click :: ((Ptr Button) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_button_get_focus_on_click"
  gtk_button_get_focus_on_click :: ((Ptr Button) -> (IO CInt))
foreign import ccall unsafe "gtk_button_set_alignment"
  gtk_button_set_alignment :: ((Ptr Button) -> (CFloat -> (CFloat -> (IO ()))))
foreign import ccall unsafe "gtk_button_get_alignment"
  gtk_button_get_alignment :: ((Ptr Button) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))
foreign import ccall safe "gtk_button_get_image"
  gtk_button_get_image :: ((Ptr Button) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_button_set_image"
  gtk_button_set_image :: ((Ptr Button) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_button_set_image_position"
  gtk_button_set_image_position :: ((Ptr Button) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_button_get_image_position"
  gtk_button_get_image_position :: ((Ptr Button) -> (IO CInt))
foreign import ccall safe "gtk_button_get_event_window"
  gtk_button_get_event_window :: ((Ptr Button) -> (IO (Ptr DrawWindow)))
foreign import ccall unsafe "gtk_position_type_get_type"
  gtk_position_type_get_type :: CULong