module Graphics.UI.Gtk.Selectors.ColorButton (
ColorButton,
ColorButtonClass,
castToColorButton, gTypeColorButton,
toColorButton,
colorButtonNew,
colorButtonNewWithColor,
colorButtonSetColor,
colorButtonGetColor,
colorButtonSetAlpha,
colorButtonGetAlpha,
colorButtonSetUseAlpha,
colorButtonGetUseAlpha,
colorButtonSetTitle,
colorButtonGetTitle,
colorButtonUseAlpha,
colorButtonTitle,
colorButtonAlpha,
onColorSet,
afterColorSet,
) 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.Structs (Color)
colorButtonNew :: IO ColorButton
colorButtonNew =
makeNewObject mkColorButton $
liftM (castPtr :: Ptr Widget -> Ptr ColorButton) $
gtk_color_button_new
colorButtonNewWithColor ::
Color
-> IO ColorButton
colorButtonNewWithColor color =
makeNewObject mkColorButton $
liftM (castPtr :: Ptr Widget -> Ptr ColorButton) $
with color $ \colorPtr ->
gtk_color_button_new_with_color
(castPtr colorPtr)
colorButtonSetColor :: ColorButtonClass self => self
-> Color
-> IO ()
colorButtonSetColor self color =
with color $ \colorPtr ->
(\(ColorButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_button_set_color argPtr1 arg2)
(toColorButton self)
(castPtr colorPtr)
colorButtonGetColor :: ColorButtonClass self => self -> IO Color
colorButtonGetColor self =
alloca $ \colorPtr ->
(\(ColorButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_button_get_color argPtr1 arg2)
(toColorButton self)
(castPtr colorPtr)
>> peek colorPtr >>= \color ->
return color
colorButtonSetAlpha :: ColorButtonClass self => self
-> Word16
-> IO ()
colorButtonSetAlpha self alpha =
(\(ColorButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_button_set_alpha argPtr1 arg2)
(toColorButton self)
(fromIntegral alpha)
colorButtonGetAlpha :: ColorButtonClass self => self
-> IO Word16
colorButtonGetAlpha self =
liftM fromIntegral $
(\(ColorButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_button_get_alpha argPtr1)
(toColorButton self)
colorButtonSetUseAlpha :: ColorButtonClass self => self
-> Bool
-> IO ()
colorButtonSetUseAlpha self useAlpha =
(\(ColorButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_button_set_use_alpha argPtr1 arg2)
(toColorButton self)
(fromBool useAlpha)
colorButtonGetUseAlpha :: ColorButtonClass self => self
-> IO Bool
colorButtonGetUseAlpha self =
liftM toBool $
(\(ColorButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_button_get_use_alpha argPtr1)
(toColorButton self)
colorButtonSetTitle :: (ColorButtonClass self, GlibString string) => self
-> string
-> IO ()
colorButtonSetTitle self title =
withUTFString title $ \titlePtr ->
(\(ColorButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_button_set_title argPtr1 arg2)
(toColorButton self)
titlePtr
colorButtonGetTitle :: (ColorButtonClass self, GlibString string) => self
-> IO string
colorButtonGetTitle self =
(\(ColorButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_button_get_title argPtr1)
(toColorButton self)
>>= peekUTFString
colorButtonUseAlpha :: ColorButtonClass self => Attr self Bool
colorButtonUseAlpha = newAttr
colorButtonGetUseAlpha
colorButtonSetUseAlpha
colorButtonTitle :: (ColorButtonClass self, GlibString string) => Attr self string
colorButtonTitle = newAttr
colorButtonGetTitle
colorButtonSetTitle
colorButtonAlpha :: ColorButtonClass self => Attr self Word16
colorButtonAlpha = newAttr
colorButtonGetAlpha
colorButtonSetAlpha
onColorSet, afterColorSet :: ColorButtonClass self => self
-> IO ()
-> IO (ConnectId self)
onColorSet = connect_NONE__NONE "color_set" False
afterColorSet = connect_NONE__NONE "color_set" True
foreign import ccall safe "gtk_color_button_new"
gtk_color_button_new :: (IO (Ptr Widget))
foreign import ccall safe "gtk_color_button_new_with_color"
gtk_color_button_new_with_color :: ((Ptr ()) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_color_button_set_color"
gtk_color_button_set_color :: ((Ptr ColorButton) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_color_button_get_color"
gtk_color_button_get_color :: ((Ptr ColorButton) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_color_button_set_alpha"
gtk_color_button_set_alpha :: ((Ptr ColorButton) -> (CUShort -> (IO ())))
foreign import ccall safe "gtk_color_button_get_alpha"
gtk_color_button_get_alpha :: ((Ptr ColorButton) -> (IO CUShort))
foreign import ccall safe "gtk_color_button_set_use_alpha"
gtk_color_button_set_use_alpha :: ((Ptr ColorButton) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_color_button_get_use_alpha"
gtk_color_button_get_use_alpha :: ((Ptr ColorButton) -> (IO CInt))
foreign import ccall safe "gtk_color_button_set_title"
gtk_color_button_set_title :: ((Ptr ColorButton) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_color_button_get_title"
gtk_color_button_get_title :: ((Ptr ColorButton) -> (IO (Ptr CChar)))