module Graphics.UI.Gtk.Selectors.ColorSelection (
ColorSelection,
ColorSelectionClass,
castToColorSelection, gTypeColorSelection,
toColorSelection,
colorSelectionNew,
colorSelectionGetCurrentAlpha,
colorSelectionSetCurrentAlpha,
colorSelectionGetCurrentColor,
colorSelectionSetCurrentColor,
colorSelectionGetHasOpacityControl,
colorSelectionSetHasOpacityControl,
colorSelectionGetHasPalette,
colorSelectionSetHasPalette,
colorSelectionGetPreviousAlpha,
colorSelectionSetPreviousAlpha,
colorSelectionGetPreviousColor,
colorSelectionSetPreviousColor,
colorSelectionIsAdjusting,
colorSelectionHasOpacityControl,
colorSelectionHasPalette,
colorSelectionCurrentAlpha,
colorSelectionPreviousAlpha,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.Attributes
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.General.Structs (Color)
colorSelectionNew :: IO ColorSelection
colorSelectionNew =
makeNewObject mkColorSelection $
liftM (castPtr :: Ptr Widget -> Ptr ColorSelection) $
gtk_color_selection_new
colorSelectionGetCurrentAlpha :: ColorSelectionClass self => self
-> IO Int
colorSelectionGetCurrentAlpha self =
liftM fromIntegral $
(\(ColorSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_get_current_alpha argPtr1)
(toColorSelection self)
colorSelectionSetCurrentAlpha :: ColorSelectionClass self => self
-> Int
-> IO ()
colorSelectionSetCurrentAlpha self alpha =
(\(ColorSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_set_current_alpha argPtr1 arg2)
(toColorSelection self)
(fromIntegral alpha)
colorSelectionGetCurrentColor :: ColorSelectionClass self => self -> IO Color
colorSelectionGetCurrentColor self =
alloca $ \colorPtr -> do
(\(ColorSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_get_current_color argPtr1 arg2)
(toColorSelection self)
(castPtr colorPtr)
peek colorPtr
colorSelectionSetCurrentColor :: ColorSelectionClass self => self
-> Color
-> IO ()
colorSelectionSetCurrentColor self color =
with color $ \colorPtr ->
(\(ColorSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_set_current_color argPtr1 arg2)
(toColorSelection self)
(castPtr colorPtr)
colorSelectionGetHasOpacityControl :: ColorSelectionClass self => self
-> IO Bool
colorSelectionGetHasOpacityControl self =
liftM toBool $
(\(ColorSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_get_has_opacity_control argPtr1)
(toColorSelection self)
colorSelectionSetHasOpacityControl :: ColorSelectionClass self => self
-> Bool
-> IO ()
colorSelectionSetHasOpacityControl self hasOpacity =
(\(ColorSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_set_has_opacity_control argPtr1 arg2)
(toColorSelection self)
(fromBool hasOpacity)
colorSelectionGetHasPalette :: ColorSelectionClass self => self
-> IO Bool
colorSelectionGetHasPalette self =
liftM toBool $
(\(ColorSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_get_has_palette argPtr1)
(toColorSelection self)
colorSelectionSetHasPalette :: ColorSelectionClass self => self
-> Bool
-> IO ()
colorSelectionSetHasPalette self hasPalette =
(\(ColorSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_set_has_palette argPtr1 arg2)
(toColorSelection self)
(fromBool hasPalette)
colorSelectionGetPreviousAlpha :: ColorSelectionClass self => self
-> IO Int
colorSelectionGetPreviousAlpha self =
liftM fromIntegral $
(\(ColorSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_get_previous_alpha argPtr1)
(toColorSelection self)
colorSelectionSetPreviousAlpha :: ColorSelectionClass self => self
-> Int
-> IO ()
colorSelectionSetPreviousAlpha self alpha =
(\(ColorSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_set_previous_alpha argPtr1 arg2)
(toColorSelection self)
(fromIntegral alpha)
colorSelectionGetPreviousColor :: ColorSelectionClass self => self -> IO Color
colorSelectionGetPreviousColor self =
alloca $ \colorPtr -> do
(\(ColorSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_get_previous_color argPtr1 arg2)
(toColorSelection self)
(castPtr colorPtr)
peek colorPtr
colorSelectionSetPreviousColor :: ColorSelectionClass self => self
-> Color -> IO ()
colorSelectionSetPreviousColor self color =
with color $ \colorPtr ->
(\(ColorSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_set_previous_color argPtr1 arg2)
(toColorSelection self)
(castPtr colorPtr)
colorSelectionIsAdjusting :: ColorSelectionClass self => self -> IO Bool
colorSelectionIsAdjusting self =
liftM toBool $
(\(ColorSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_color_selection_is_adjusting argPtr1)
(toColorSelection self)
colorSelectionHasOpacityControl :: ColorSelectionClass self => Attr self Bool
colorSelectionHasOpacityControl = newAttr
colorSelectionGetHasOpacityControl
colorSelectionSetHasOpacityControl
colorSelectionHasPalette :: ColorSelectionClass self => Attr self Bool
colorSelectionHasPalette = newAttr
colorSelectionGetHasPalette
colorSelectionSetHasPalette
colorSelectionCurrentAlpha :: ColorSelectionClass self => Attr self Int
colorSelectionCurrentAlpha = newAttr
colorSelectionGetCurrentAlpha
colorSelectionSetCurrentAlpha
colorSelectionPreviousAlpha :: ColorSelectionClass self => Attr self Int
colorSelectionPreviousAlpha = newAttr
colorSelectionGetPreviousAlpha
colorSelectionSetPreviousAlpha
foreign import ccall unsafe "gtk_color_selection_new"
gtk_color_selection_new :: (IO (Ptr Widget))
foreign import ccall unsafe "gtk_color_selection_get_current_alpha"
gtk_color_selection_get_current_alpha :: ((Ptr ColorSelection) -> (IO CUShort))
foreign import ccall safe "gtk_color_selection_set_current_alpha"
gtk_color_selection_set_current_alpha :: ((Ptr ColorSelection) -> (CUShort -> (IO ())))
foreign import ccall unsafe "gtk_color_selection_get_current_color"
gtk_color_selection_get_current_color :: ((Ptr ColorSelection) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_color_selection_set_current_color"
gtk_color_selection_set_current_color :: ((Ptr ColorSelection) -> ((Ptr ()) -> (IO ())))
foreign import ccall unsafe "gtk_color_selection_get_has_opacity_control"
gtk_color_selection_get_has_opacity_control :: ((Ptr ColorSelection) -> (IO CInt))
foreign import ccall safe "gtk_color_selection_set_has_opacity_control"
gtk_color_selection_set_has_opacity_control :: ((Ptr ColorSelection) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_color_selection_get_has_palette"
gtk_color_selection_get_has_palette :: ((Ptr ColorSelection) -> (IO CInt))
foreign import ccall safe "gtk_color_selection_set_has_palette"
gtk_color_selection_set_has_palette :: ((Ptr ColorSelection) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_color_selection_get_previous_alpha"
gtk_color_selection_get_previous_alpha :: ((Ptr ColorSelection) -> (IO CUShort))
foreign import ccall safe "gtk_color_selection_set_previous_alpha"
gtk_color_selection_set_previous_alpha :: ((Ptr ColorSelection) -> (CUShort -> (IO ())))
foreign import ccall unsafe "gtk_color_selection_get_previous_color"
gtk_color_selection_get_previous_color :: ((Ptr ColorSelection) -> ((Ptr ()) -> (IO ())))
foreign import ccall safe "gtk_color_selection_set_previous_color"
gtk_color_selection_set_previous_color :: ((Ptr ColorSelection) -> ((Ptr ()) -> (IO ())))
foreign import ccall unsafe "gtk_color_selection_is_adjusting"
gtk_color_selection_is_adjusting :: ((Ptr ColorSelection) -> (IO CInt))