module Graphics.UI.Gtk.ActionMenuToolbar.ToggleAction (
ToggleAction,
ToggleActionClass,
castToToggleAction, gTypeToggleAction,
toToggleAction,
toggleActionNew,
toggleActionToggled,
toggleActionSetActive,
toggleActionGetActive,
toggleActionSetDrawAsRadio,
toggleActionGetDrawAsRadio,
toggleActionDrawAsRadio,
toggleActionActive,
actionToggled,
onActionToggled,
afterActionToggled,
) 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.Types
import Graphics.UI.Gtk.Signals
import Graphics.UI.Gtk.General.StockItems
toggleActionNew :: GlibString string
=> string
-> string
-> Maybe string
-> Maybe StockId
-> IO ToggleAction
toggleActionNew name label tooltip stockId =
wrapNewGObject mkToggleAction $
maybeWith withUTFString stockId $ \stockIdPtr ->
maybeWith withUTFString tooltip $ \tooltipPtr ->
withUTFString label $ \labelPtr ->
withUTFString name $ \namePtr ->
gtk_toggle_action_new
namePtr
labelPtr
tooltipPtr
stockIdPtr
toggleActionToggled :: ToggleActionClass self => self -> IO ()
toggleActionToggled self =
(\(ToggleAction arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_toggle_action_toggled argPtr1)
(toToggleAction self)
toggleActionSetActive :: ToggleActionClass self => self
-> Bool
-> IO ()
toggleActionSetActive self isActive =
(\(ToggleAction arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_toggle_action_set_active argPtr1 arg2)
(toToggleAction self)
(fromBool isActive)
toggleActionGetActive :: ToggleActionClass self => self -> IO Bool
toggleActionGetActive self =
liftM toBool $
(\(ToggleAction arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_toggle_action_get_active argPtr1)
(toToggleAction self)
toggleActionSetDrawAsRadio :: ToggleActionClass self => self -> Bool -> IO ()
toggleActionSetDrawAsRadio self drawAsRadio =
(\(ToggleAction arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_toggle_action_set_draw_as_radio argPtr1 arg2)
(toToggleAction self)
(fromBool drawAsRadio)
toggleActionGetDrawAsRadio :: ToggleActionClass self => self -> IO Bool
toggleActionGetDrawAsRadio self =
liftM toBool $
(\(ToggleAction arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_toggle_action_get_draw_as_radio argPtr1)
(toToggleAction self)
toggleActionDrawAsRadio :: ToggleActionClass self => Attr self Bool
toggleActionDrawAsRadio = newAttr
toggleActionGetDrawAsRadio
toggleActionSetDrawAsRadio
toggleActionActive :: ToggleActionClass self => Attr self Bool
toggleActionActive = newAttrFromBoolProperty "active"
actionToggled :: ToggleActionClass self => Signal self (IO ())
actionToggled = Signal (connect_NONE__NONE "toggled")
onActionToggled :: ToggleActionClass self => self
-> IO ()
-> IO (ConnectId self)
onActionToggled = connect_NONE__NONE "toggled" False
afterActionToggled :: ToggleActionClass self => self
-> IO ()
-> IO (ConnectId self)
afterActionToggled = connect_NONE__NONE "toggled" True
foreign import ccall safe "gtk_toggle_action_new"
gtk_toggle_action_new :: ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO (Ptr ToggleAction))))))
foreign import ccall safe "gtk_toggle_action_toggled"
gtk_toggle_action_toggled :: ((Ptr ToggleAction) -> (IO ()))
foreign import ccall safe "gtk_toggle_action_set_active"
gtk_toggle_action_set_active :: ((Ptr ToggleAction) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_toggle_action_get_active"
gtk_toggle_action_get_active :: ((Ptr ToggleAction) -> (IO CInt))
foreign import ccall safe "gtk_toggle_action_set_draw_as_radio"
gtk_toggle_action_set_draw_as_radio :: ((Ptr ToggleAction) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_toggle_action_get_draw_as_radio"
gtk_toggle_action_get_draw_as_radio :: ((Ptr ToggleAction) -> (IO CInt))