{-# LINE 2 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
module Graphics.UI.Gtk.Buttons.ToggleButton (
ToggleButton,
ToggleButtonClass,
castToToggleButton, gTypeToggleButton,
toToggleButton,
toggleButtonNew,
toggleButtonNewWithLabel,
toggleButtonNewWithMnemonic,
toggleButtonSetMode,
toggleButtonGetMode,
toggleButtonToggled,
toggleButtonGetActive,
toggleButtonSetActive,
toggleButtonGetInconsistent,
toggleButtonSetInconsistent,
toggleButtonActive,
toggleButtonInconsistent,
toggleButtonDrawIndicator,
toggleButtonMode,
toggled,
) 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
{-# LINE 103 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
import Graphics.UI.Gtk.Signals
{-# LINE 104 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
{-# LINE 106 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
toggleButtonNew :: IO ToggleButton
toggleButtonNew :: IO ToggleButton
toggleButtonNew =
(ForeignPtr ToggleButton -> ToggleButton,
FinalizerPtr ToggleButton)
-> IO (Ptr ToggleButton) -> IO ToggleButton
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr ToggleButton -> ToggleButton,
FinalizerPtr ToggleButton)
forall {a}.
(ForeignPtr ToggleButton -> ToggleButton, FinalizerPtr a)
mkToggleButton (IO (Ptr ToggleButton) -> IO ToggleButton)
-> IO (Ptr ToggleButton) -> IO ToggleButton
forall a b. (a -> b) -> a -> b
$
(Ptr Widget -> Ptr ToggleButton)
-> IO (Ptr Widget) -> IO (Ptr ToggleButton)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Ptr Widget -> Ptr ToggleButton
forall a b. Ptr a -> Ptr b
castPtr :: Ptr Widget -> Ptr ToggleButton) (IO (Ptr Widget) -> IO (Ptr ToggleButton))
-> IO (Ptr Widget) -> IO (Ptr ToggleButton)
forall a b. (a -> b) -> a -> b
$
IO (Ptr Widget)
gtk_toggle_button_new
{-# LINE 118 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
toggleButtonNewWithLabel :: GlibString string
=> string
-> IO ToggleButton
toggleButtonNewWithLabel :: forall string. GlibString string => string -> IO ToggleButton
toggleButtonNewWithLabel string
label =
(ForeignPtr ToggleButton -> ToggleButton,
FinalizerPtr ToggleButton)
-> IO (Ptr ToggleButton) -> IO ToggleButton
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr ToggleButton -> ToggleButton,
FinalizerPtr ToggleButton)
forall {a}.
(ForeignPtr ToggleButton -> ToggleButton, FinalizerPtr a)
mkToggleButton (IO (Ptr ToggleButton) -> IO ToggleButton)
-> IO (Ptr ToggleButton) -> IO ToggleButton
forall a b. (a -> b) -> a -> b
$
(Ptr Widget -> Ptr ToggleButton)
-> IO (Ptr Widget) -> IO (Ptr ToggleButton)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Ptr Widget -> Ptr ToggleButton
forall a b. Ptr a -> Ptr b
castPtr :: Ptr Widget -> Ptr ToggleButton) (IO (Ptr Widget) -> IO (Ptr ToggleButton))
-> IO (Ptr Widget) -> IO (Ptr ToggleButton)
forall a b. (a -> b) -> a -> b
$
string -> (CString -> IO (Ptr Widget)) -> IO (Ptr Widget)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
label ((CString -> IO (Ptr Widget)) -> IO (Ptr Widget))
-> (CString -> IO (Ptr Widget)) -> IO (Ptr Widget)
forall a b. (a -> b) -> a -> b
$ \CString
labelPtr ->
CString -> IO (Ptr Widget)
gtk_toggle_button_new_with_label
{-# LINE 130 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
labelPtr
toggleButtonNewWithMnemonic :: GlibString string
=> string
-> IO ToggleButton
toggleButtonNewWithMnemonic :: forall string. GlibString string => string -> IO ToggleButton
toggleButtonNewWithMnemonic string
label =
(ForeignPtr ToggleButton -> ToggleButton,
FinalizerPtr ToggleButton)
-> IO (Ptr ToggleButton) -> IO ToggleButton
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr ToggleButton -> ToggleButton,
FinalizerPtr ToggleButton)
forall {a}.
(ForeignPtr ToggleButton -> ToggleButton, FinalizerPtr a)
mkToggleButton (IO (Ptr ToggleButton) -> IO ToggleButton)
-> IO (Ptr ToggleButton) -> IO ToggleButton
forall a b. (a -> b) -> a -> b
$
(Ptr Widget -> Ptr ToggleButton)
-> IO (Ptr Widget) -> IO (Ptr ToggleButton)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Ptr Widget -> Ptr ToggleButton
forall a b. Ptr a -> Ptr b
castPtr :: Ptr Widget -> Ptr ToggleButton) (IO (Ptr Widget) -> IO (Ptr ToggleButton))
-> IO (Ptr Widget) -> IO (Ptr ToggleButton)
forall a b. (a -> b) -> a -> b
$
string -> (CString -> IO (Ptr Widget)) -> IO (Ptr Widget)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
label ((CString -> IO (Ptr Widget)) -> IO (Ptr Widget))
-> (CString -> IO (Ptr Widget)) -> IO (Ptr Widget)
forall a b. (a -> b) -> a -> b
$ \CString
labelPtr ->
CString -> IO (Ptr Widget)
gtk_toggle_button_new_with_mnemonic
{-# LINE 146 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
labelPtr
toggleButtonSetMode :: ToggleButtonClass self => self
-> Bool
-> IO ()
toggleButtonSetMode :: forall self. ToggleButtonClass self => self -> Bool -> IO ()
toggleButtonSetMode self
self Bool
drawIndicator =
(\(ToggleButton ForeignPtr ToggleButton
arg1) CInt
arg2 -> ForeignPtr ToggleButton -> (Ptr ToggleButton -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ToggleButton
arg1 ((Ptr ToggleButton -> IO ()) -> IO ())
-> (Ptr ToggleButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ToggleButton
argPtr1 ->Ptr ToggleButton -> CInt -> IO ()
gtk_toggle_button_set_mode Ptr ToggleButton
argPtr1 CInt
arg2)
{-# LINE 166 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
(toToggleButton self)
(Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
drawIndicator)
toggleButtonGetMode :: ToggleButtonClass self => self
-> IO Bool
toggleButtonGetMode :: forall self. ToggleButtonClass self => self -> IO Bool
toggleButtonGetMode self
self =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(ToggleButton ForeignPtr ToggleButton
arg1) -> ForeignPtr ToggleButton -> (Ptr ToggleButton -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ToggleButton
arg1 ((Ptr ToggleButton -> IO CInt) -> IO CInt)
-> (Ptr ToggleButton -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr ToggleButton
argPtr1 ->Ptr ToggleButton -> IO CInt
gtk_toggle_button_get_mode Ptr ToggleButton
argPtr1)
{-# LINE 178 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
(toToggleButton self)
toggleButtonToggled :: ToggleButtonClass self => self -> IO ()
toggleButtonToggled :: forall self. ToggleButtonClass self => self -> IO ()
toggleButtonToggled self
self =
(\(ToggleButton ForeignPtr ToggleButton
arg1) -> ForeignPtr ToggleButton -> (Ptr ToggleButton -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ToggleButton
arg1 ((Ptr ToggleButton -> IO ()) -> IO ())
-> (Ptr ToggleButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ToggleButton
argPtr1 ->Ptr ToggleButton -> IO ()
gtk_toggle_button_toggled Ptr ToggleButton
argPtr1)
{-# LINE 186 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
(toToggleButton self)
toggleButtonGetActive :: ToggleButtonClass self => self -> IO Bool
toggleButtonGetActive :: forall self. ToggleButtonClass self => self -> IO Bool
toggleButtonGetActive self
self =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(ToggleButton ForeignPtr ToggleButton
arg1) -> ForeignPtr ToggleButton -> (Ptr ToggleButton -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ToggleButton
arg1 ((Ptr ToggleButton -> IO CInt) -> IO CInt)
-> (Ptr ToggleButton -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr ToggleButton
argPtr1 ->Ptr ToggleButton -> IO CInt
gtk_toggle_button_get_active Ptr ToggleButton
argPtr1)
{-# LINE 195 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
(toToggleButton self)
toggleButtonSetActive :: ToggleButtonClass self => self
-> Bool
-> IO ()
toggleButtonSetActive :: forall self. ToggleButtonClass self => self -> Bool -> IO ()
toggleButtonSetActive self
self Bool
isActive =
(\(ToggleButton ForeignPtr ToggleButton
arg1) CInt
arg2 -> ForeignPtr ToggleButton -> (Ptr ToggleButton -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ToggleButton
arg1 ((Ptr ToggleButton -> IO ()) -> IO ())
-> (Ptr ToggleButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ToggleButton
argPtr1 ->Ptr ToggleButton -> CInt -> IO ()
gtk_toggle_button_set_active Ptr ToggleButton
argPtr1 CInt
arg2)
{-# LINE 206 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
(toToggleButton self)
(Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
isActive)
toggleButtonGetInconsistent :: ToggleButtonClass self => self
-> IO Bool
toggleButtonGetInconsistent :: forall self. ToggleButtonClass self => self -> IO Bool
toggleButtonGetInconsistent self
self =
(CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
(\(ToggleButton ForeignPtr ToggleButton
arg1) -> ForeignPtr ToggleButton -> (Ptr ToggleButton -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ToggleButton
arg1 ((Ptr ToggleButton -> IO CInt) -> IO CInt)
-> (Ptr ToggleButton -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr ToggleButton
argPtr1 ->Ptr ToggleButton -> IO CInt
gtk_toggle_button_get_inconsistent Ptr ToggleButton
argPtr1)
{-# LINE 217 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
(toToggleButton self)
toggleButtonSetInconsistent :: ToggleButtonClass self => self
-> Bool
-> IO ()
toggleButtonSetInconsistent :: forall self. ToggleButtonClass self => self -> Bool -> IO ()
toggleButtonSetInconsistent self
self Bool
setting =
(\(ToggleButton ForeignPtr ToggleButton
arg1) CInt
arg2 -> ForeignPtr ToggleButton -> (Ptr ToggleButton -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ToggleButton
arg1 ((Ptr ToggleButton -> IO ()) -> IO ())
-> (Ptr ToggleButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ToggleButton
argPtr1 ->Ptr ToggleButton -> CInt -> IO ()
gtk_toggle_button_set_inconsistent Ptr ToggleButton
argPtr1 CInt
arg2)
{-# LINE 233 "./Graphics/UI/Gtk/Buttons/ToggleButton.chs" #-}
(toToggleButton self)
(Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
setting)
toggleButtonActive :: ToggleButtonClass self => Attr self Bool
toggleButtonActive :: forall self. ToggleButtonClass self => Attr self Bool
toggleButtonActive = (self -> IO Bool)
-> (self -> Bool -> IO ()) -> ReadWriteAttr self Bool Bool
forall o a b.
(o -> IO a) -> (o -> b -> IO ()) -> ReadWriteAttr o a b
newAttr
self -> IO Bool
forall self. ToggleButtonClass self => self -> IO Bool
toggleButtonGetActive
self -> Bool -> IO ()
forall self. ToggleButtonClass self => self -> Bool -> IO ()
toggleButtonSetActive
toggleButtonInconsistent :: ToggleButtonClass self => Attr self Bool
toggleButtonInconsistent :: forall self. ToggleButtonClass self => Attr self Bool
toggleButtonInconsistent = (self -> IO Bool)
-> (self -> Bool -> IO ()) -> ReadWriteAttr self Bool Bool
forall o a b.
(o -> IO a) -> (o -> b -> IO ()) -> ReadWriteAttr o a b
newAttr
self -> IO Bool
forall self. ToggleButtonClass self => self -> IO Bool
toggleButtonGetInconsistent
self -> Bool -> IO ()
forall self. ToggleButtonClass self => self -> Bool -> IO ()
toggleButtonSetInconsistent
toggleButtonDrawIndicator :: ToggleButtonClass self => Attr self Bool
toggleButtonDrawIndicator :: forall self. ToggleButtonClass self => Attr self Bool
toggleButtonDrawIndicator = String -> Attr self Bool
forall gobj. GObjectClass gobj => String -> Attr gobj Bool
newAttrFromBoolProperty String
"draw-indicator"
toggleButtonMode :: ToggleButtonClass self => Attr self Bool
toggleButtonMode :: forall self. ToggleButtonClass self => Attr self Bool
toggleButtonMode = (self -> IO Bool)
-> (self -> Bool -> IO ()) -> ReadWriteAttr self Bool Bool
forall o a b.
(o -> IO a) -> (o -> b -> IO ()) -> ReadWriteAttr o a b
newAttr
self -> IO Bool
forall self. ToggleButtonClass self => self -> IO Bool
toggleButtonGetMode
self -> Bool -> IO ()
forall self. ToggleButtonClass self => self -> Bool -> IO ()
toggleButtonSetMode
toggled :: ToggleButtonClass self => Signal self (IO ())
toggled :: forall self. ToggleButtonClass self => Signal self (IO ())
toggled = (Bool -> self -> IO () -> IO (ConnectId self))
-> Signal self (IO ())
forall object handler.
(Bool -> object -> handler -> IO (ConnectId object))
-> Signal object handler
Signal (String -> Bool -> self -> IO () -> IO (ConnectId self)
forall obj.
GObjectClass obj =>
String -> Bool -> obj -> IO () -> IO (ConnectId obj)
connect_NONE__NONE String
"toggled")
foreign import ccall unsafe "gtk_toggle_button_new"
gtk_toggle_button_new :: (IO (Ptr Widget))
foreign import ccall unsafe "gtk_toggle_button_new_with_label"
gtk_toggle_button_new_with_label :: ((Ptr CChar) -> (IO (Ptr Widget)))
foreign import ccall unsafe "gtk_toggle_button_new_with_mnemonic"
gtk_toggle_button_new_with_mnemonic :: ((Ptr CChar) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_toggle_button_set_mode"
gtk_toggle_button_set_mode :: ((Ptr ToggleButton) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_toggle_button_get_mode"
gtk_toggle_button_get_mode :: ((Ptr ToggleButton) -> (IO CInt))
foreign import ccall safe "gtk_toggle_button_toggled"
gtk_toggle_button_toggled :: ((Ptr ToggleButton) -> (IO ()))
foreign import ccall unsafe "gtk_toggle_button_get_active"
gtk_toggle_button_get_active :: ((Ptr ToggleButton) -> (IO CInt))
foreign import ccall safe "gtk_toggle_button_set_active"
gtk_toggle_button_set_active :: ((Ptr ToggleButton) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_toggle_button_get_inconsistent"
gtk_toggle_button_get_inconsistent :: ((Ptr ToggleButton) -> (IO CInt))
foreign import ccall safe "gtk_toggle_button_set_inconsistent"
gtk_toggle_button_set_inconsistent :: ((Ptr ToggleButton) -> (CInt -> (IO ())))