{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gtk.Objects.ColorSelection
    ( 

-- * Exported types
    ColorSelection(..)                      ,
    ColorSelectionK                         ,
    toColorSelection                        ,
    noColorSelection                        ,


 -- * Methods
-- ** colorSelectionGetCurrentAlpha
    colorSelectionGetCurrentAlpha           ,


-- ** colorSelectionGetCurrentColor
    colorSelectionGetCurrentColor           ,


-- ** colorSelectionGetCurrentRgba
    colorSelectionGetCurrentRgba            ,


-- ** colorSelectionGetHasOpacityControl
    colorSelectionGetHasOpacityControl      ,


-- ** colorSelectionGetHasPalette
    colorSelectionGetHasPalette             ,


-- ** colorSelectionGetPreviousAlpha
    colorSelectionGetPreviousAlpha          ,


-- ** colorSelectionGetPreviousColor
    colorSelectionGetPreviousColor          ,


-- ** colorSelectionGetPreviousRgba
    colorSelectionGetPreviousRgba           ,


-- ** colorSelectionIsAdjusting
    colorSelectionIsAdjusting               ,


-- ** colorSelectionNew
    colorSelectionNew                       ,


-- ** colorSelectionPaletteFromString
    colorSelectionPaletteFromString         ,


-- ** colorSelectionPaletteToString
    colorSelectionPaletteToString           ,


-- ** colorSelectionSetCurrentAlpha
    colorSelectionSetCurrentAlpha           ,


-- ** colorSelectionSetCurrentColor
    colorSelectionSetCurrentColor           ,


-- ** colorSelectionSetCurrentRgba
    colorSelectionSetCurrentRgba            ,


-- ** colorSelectionSetHasOpacityControl
    colorSelectionSetHasOpacityControl      ,


-- ** colorSelectionSetHasPalette
    colorSelectionSetHasPalette             ,


-- ** colorSelectionSetPreviousAlpha
    colorSelectionSetPreviousAlpha          ,


-- ** colorSelectionSetPreviousColor
    colorSelectionSetPreviousColor          ,


-- ** colorSelectionSetPreviousRgba
    colorSelectionSetPreviousRgba           ,




 -- * Properties
-- ** CurrentAlpha
    ColorSelectionCurrentAlphaPropertyInfo  ,
    constructColorSelectionCurrentAlpha     ,
    getColorSelectionCurrentAlpha           ,
    setColorSelectionCurrentAlpha           ,


-- ** CurrentColor
    ColorSelectionCurrentColorPropertyInfo  ,
    constructColorSelectionCurrentColor     ,
    getColorSelectionCurrentColor           ,
    setColorSelectionCurrentColor           ,


-- ** CurrentRgba
    ColorSelectionCurrentRgbaPropertyInfo   ,
    constructColorSelectionCurrentRgba      ,
    getColorSelectionCurrentRgba            ,
    setColorSelectionCurrentRgba            ,


-- ** HasOpacityControl
    ColorSelectionHasOpacityControlPropertyInfo,
    constructColorSelectionHasOpacityControl,
    getColorSelectionHasOpacityControl      ,
    setColorSelectionHasOpacityControl      ,


-- ** HasPalette
    ColorSelectionHasPalettePropertyInfo    ,
    constructColorSelectionHasPalette       ,
    getColorSelectionHasPalette             ,
    setColorSelectionHasPalette             ,




 -- * Signals
-- ** ColorChanged
    ColorSelectionColorChangedCallback      ,
    ColorSelectionColorChangedCallbackC     ,
    ColorSelectionColorChangedSignalInfo    ,
    afterColorSelectionColorChanged         ,
    colorSelectionColorChangedCallbackWrapper,
    colorSelectionColorChangedClosure       ,
    mkColorSelectionColorChangedCallback    ,
    noColorSelectionColorChangedCallback    ,
    onColorSelectionColorChanged            ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.Atk as Atk
import qualified GI.GObject as GObject
import qualified GI.Gdk as Gdk

newtype ColorSelection = ColorSelection (ForeignPtr ColorSelection)
foreign import ccall "gtk_color_selection_get_type"
    c_gtk_color_selection_get_type :: IO GType

type instance ParentTypes ColorSelection = ColorSelectionParentTypes
type ColorSelectionParentTypes = '[Box, Container, Widget, GObject.Object, Atk.ImplementorIface, Buildable, Orientable]

instance GObject ColorSelection where
    gobjectIsInitiallyUnowned _ = True
    gobjectType _ = c_gtk_color_selection_get_type
    

class GObject o => ColorSelectionK o
instance (GObject o, IsDescendantOf ColorSelection o) => ColorSelectionK o

toColorSelection :: ColorSelectionK o => o -> IO ColorSelection
toColorSelection = unsafeCastTo ColorSelection

noColorSelection :: Maybe ColorSelection
noColorSelection = Nothing

-- signal ColorSelection::color-changed
type ColorSelectionColorChangedCallback =
    IO ()

noColorSelectionColorChangedCallback :: Maybe ColorSelectionColorChangedCallback
noColorSelectionColorChangedCallback = Nothing

type ColorSelectionColorChangedCallbackC =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkColorSelectionColorChangedCallback :: ColorSelectionColorChangedCallbackC -> IO (FunPtr ColorSelectionColorChangedCallbackC)

colorSelectionColorChangedClosure :: ColorSelectionColorChangedCallback -> IO Closure
colorSelectionColorChangedClosure cb = newCClosure =<< mkColorSelectionColorChangedCallback wrapped
    where wrapped = colorSelectionColorChangedCallbackWrapper cb

colorSelectionColorChangedCallbackWrapper ::
    ColorSelectionColorChangedCallback ->
    Ptr () ->
    Ptr () ->
    IO ()
colorSelectionColorChangedCallbackWrapper _cb _ _ = do
    _cb 

onColorSelectionColorChanged :: (GObject a, MonadIO m) => a -> ColorSelectionColorChangedCallback -> m SignalHandlerId
onColorSelectionColorChanged obj cb = liftIO $ connectColorSelectionColorChanged obj cb SignalConnectBefore
afterColorSelectionColorChanged :: (GObject a, MonadIO m) => a -> ColorSelectionColorChangedCallback -> m SignalHandlerId
afterColorSelectionColorChanged obj cb = connectColorSelectionColorChanged obj cb SignalConnectAfter

connectColorSelectionColorChanged :: (GObject a, MonadIO m) =>
                                     a -> ColorSelectionColorChangedCallback -> SignalConnectMode -> m SignalHandlerId
connectColorSelectionColorChanged obj cb after = liftIO $ do
    cb' <- mkColorSelectionColorChangedCallback (colorSelectionColorChangedCallbackWrapper cb)
    connectSignalFunPtr obj "color-changed" cb' after

-- VVV Prop "current-alpha"
   -- Type: TBasicType TUInt32
   -- Flags: [PropertyReadable,PropertyWritable]

getColorSelectionCurrentAlpha :: (MonadIO m, ColorSelectionK o) => o -> m Word32
getColorSelectionCurrentAlpha obj = liftIO $ getObjectPropertyCUInt obj "current-alpha"

setColorSelectionCurrentAlpha :: (MonadIO m, ColorSelectionK o) => o -> Word32 -> m ()
setColorSelectionCurrentAlpha obj val = liftIO $ setObjectPropertyCUInt obj "current-alpha" val

constructColorSelectionCurrentAlpha :: Word32 -> IO ([Char], GValue)
constructColorSelectionCurrentAlpha val = constructObjectPropertyCUInt "current-alpha" val

data ColorSelectionCurrentAlphaPropertyInfo
instance AttrInfo ColorSelectionCurrentAlphaPropertyInfo where
    type AttrAllowedOps ColorSelectionCurrentAlphaPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ColorSelectionCurrentAlphaPropertyInfo = (~) Word32
    type AttrBaseTypeConstraint ColorSelectionCurrentAlphaPropertyInfo = ColorSelectionK
    type AttrGetType ColorSelectionCurrentAlphaPropertyInfo = Word32
    type AttrLabel ColorSelectionCurrentAlphaPropertyInfo = "ColorSelection::current-alpha"
    attrGet _ = getColorSelectionCurrentAlpha
    attrSet _ = setColorSelectionCurrentAlpha
    attrConstruct _ = constructColorSelectionCurrentAlpha

-- VVV Prop "current-color"
   -- Type: TInterface "Gdk" "Color"
   -- Flags: [PropertyReadable,PropertyWritable]

getColorSelectionCurrentColor :: (MonadIO m, ColorSelectionK o) => o -> m Gdk.Color
getColorSelectionCurrentColor obj = liftIO $ getObjectPropertyBoxed obj "current-color" Gdk.Color

setColorSelectionCurrentColor :: (MonadIO m, ColorSelectionK o) => o -> Gdk.Color -> m ()
setColorSelectionCurrentColor obj val = liftIO $ setObjectPropertyBoxed obj "current-color" val

constructColorSelectionCurrentColor :: Gdk.Color -> IO ([Char], GValue)
constructColorSelectionCurrentColor val = constructObjectPropertyBoxed "current-color" val

data ColorSelectionCurrentColorPropertyInfo
instance AttrInfo ColorSelectionCurrentColorPropertyInfo where
    type AttrAllowedOps ColorSelectionCurrentColorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ColorSelectionCurrentColorPropertyInfo = (~) Gdk.Color
    type AttrBaseTypeConstraint ColorSelectionCurrentColorPropertyInfo = ColorSelectionK
    type AttrGetType ColorSelectionCurrentColorPropertyInfo = Gdk.Color
    type AttrLabel ColorSelectionCurrentColorPropertyInfo = "ColorSelection::current-color"
    attrGet _ = getColorSelectionCurrentColor
    attrSet _ = setColorSelectionCurrentColor
    attrConstruct _ = constructColorSelectionCurrentColor

-- VVV Prop "current-rgba"
   -- Type: TInterface "Gdk" "RGBA"
   -- Flags: [PropertyReadable,PropertyWritable]

getColorSelectionCurrentRgba :: (MonadIO m, ColorSelectionK o) => o -> m Gdk.RGBA
getColorSelectionCurrentRgba obj = liftIO $ getObjectPropertyBoxed obj "current-rgba" Gdk.RGBA

setColorSelectionCurrentRgba :: (MonadIO m, ColorSelectionK o) => o -> Gdk.RGBA -> m ()
setColorSelectionCurrentRgba obj val = liftIO $ setObjectPropertyBoxed obj "current-rgba" val

constructColorSelectionCurrentRgba :: Gdk.RGBA -> IO ([Char], GValue)
constructColorSelectionCurrentRgba val = constructObjectPropertyBoxed "current-rgba" val

data ColorSelectionCurrentRgbaPropertyInfo
instance AttrInfo ColorSelectionCurrentRgbaPropertyInfo where
    type AttrAllowedOps ColorSelectionCurrentRgbaPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ColorSelectionCurrentRgbaPropertyInfo = (~) Gdk.RGBA
    type AttrBaseTypeConstraint ColorSelectionCurrentRgbaPropertyInfo = ColorSelectionK
    type AttrGetType ColorSelectionCurrentRgbaPropertyInfo = Gdk.RGBA
    type AttrLabel ColorSelectionCurrentRgbaPropertyInfo = "ColorSelection::current-rgba"
    attrGet _ = getColorSelectionCurrentRgba
    attrSet _ = setColorSelectionCurrentRgba
    attrConstruct _ = constructColorSelectionCurrentRgba

-- VVV Prop "has-opacity-control"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getColorSelectionHasOpacityControl :: (MonadIO m, ColorSelectionK o) => o -> m Bool
getColorSelectionHasOpacityControl obj = liftIO $ getObjectPropertyBool obj "has-opacity-control"

setColorSelectionHasOpacityControl :: (MonadIO m, ColorSelectionK o) => o -> Bool -> m ()
setColorSelectionHasOpacityControl obj val = liftIO $ setObjectPropertyBool obj "has-opacity-control" val

constructColorSelectionHasOpacityControl :: Bool -> IO ([Char], GValue)
constructColorSelectionHasOpacityControl val = constructObjectPropertyBool "has-opacity-control" val

data ColorSelectionHasOpacityControlPropertyInfo
instance AttrInfo ColorSelectionHasOpacityControlPropertyInfo where
    type AttrAllowedOps ColorSelectionHasOpacityControlPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ColorSelectionHasOpacityControlPropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ColorSelectionHasOpacityControlPropertyInfo = ColorSelectionK
    type AttrGetType ColorSelectionHasOpacityControlPropertyInfo = Bool
    type AttrLabel ColorSelectionHasOpacityControlPropertyInfo = "ColorSelection::has-opacity-control"
    attrGet _ = getColorSelectionHasOpacityControl
    attrSet _ = setColorSelectionHasOpacityControl
    attrConstruct _ = constructColorSelectionHasOpacityControl

-- VVV Prop "has-palette"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]

getColorSelectionHasPalette :: (MonadIO m, ColorSelectionK o) => o -> m Bool
getColorSelectionHasPalette obj = liftIO $ getObjectPropertyBool obj "has-palette"

setColorSelectionHasPalette :: (MonadIO m, ColorSelectionK o) => o -> Bool -> m ()
setColorSelectionHasPalette obj val = liftIO $ setObjectPropertyBool obj "has-palette" val

constructColorSelectionHasPalette :: Bool -> IO ([Char], GValue)
constructColorSelectionHasPalette val = constructObjectPropertyBool "has-palette" val

data ColorSelectionHasPalettePropertyInfo
instance AttrInfo ColorSelectionHasPalettePropertyInfo where
    type AttrAllowedOps ColorSelectionHasPalettePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrSetTypeConstraint ColorSelectionHasPalettePropertyInfo = (~) Bool
    type AttrBaseTypeConstraint ColorSelectionHasPalettePropertyInfo = ColorSelectionK
    type AttrGetType ColorSelectionHasPalettePropertyInfo = Bool
    type AttrLabel ColorSelectionHasPalettePropertyInfo = "ColorSelection::has-palette"
    attrGet _ = getColorSelectionHasPalette
    attrSet _ = setColorSelectionHasPalette
    attrConstruct _ = constructColorSelectionHasPalette

type instance AttributeList ColorSelection = ColorSelectionAttributeList
type ColorSelectionAttributeList = ('[ '("app-paintable", WidgetAppPaintablePropertyInfo), '("baseline-position", BoxBaselinePositionPropertyInfo), '("border-width", ContainerBorderWidthPropertyInfo), '("can-default", WidgetCanDefaultPropertyInfo), '("can-focus", WidgetCanFocusPropertyInfo), '("child", ContainerChildPropertyInfo), '("composite-child", WidgetCompositeChildPropertyInfo), '("current-alpha", ColorSelectionCurrentAlphaPropertyInfo), '("current-color", ColorSelectionCurrentColorPropertyInfo), '("current-rgba", ColorSelectionCurrentRgbaPropertyInfo), '("double-buffered", WidgetDoubleBufferedPropertyInfo), '("events", WidgetEventsPropertyInfo), '("expand", WidgetExpandPropertyInfo), '("halign", WidgetHalignPropertyInfo), '("has-default", WidgetHasDefaultPropertyInfo), '("has-focus", WidgetHasFocusPropertyInfo), '("has-opacity-control", ColorSelectionHasOpacityControlPropertyInfo), '("has-palette", ColorSelectionHasPalettePropertyInfo), '("has-tooltip", WidgetHasTooltipPropertyInfo), '("height-request", WidgetHeightRequestPropertyInfo), '("hexpand", WidgetHexpandPropertyInfo), '("hexpand-set", WidgetHexpandSetPropertyInfo), '("homogeneous", BoxHomogeneousPropertyInfo), '("is-focus", WidgetIsFocusPropertyInfo), '("margin", WidgetMarginPropertyInfo), '("margin-bottom", WidgetMarginBottomPropertyInfo), '("margin-end", WidgetMarginEndPropertyInfo), '("margin-left", WidgetMarginLeftPropertyInfo), '("margin-right", WidgetMarginRightPropertyInfo), '("margin-start", WidgetMarginStartPropertyInfo), '("margin-top", WidgetMarginTopPropertyInfo), '("name", WidgetNamePropertyInfo), '("no-show-all", WidgetNoShowAllPropertyInfo), '("opacity", WidgetOpacityPropertyInfo), '("orientation", OrientableOrientationPropertyInfo), '("parent", WidgetParentPropertyInfo), '("receives-default", WidgetReceivesDefaultPropertyInfo), '("resize-mode", ContainerResizeModePropertyInfo), '("scale-factor", WidgetScaleFactorPropertyInfo), '("sensitive", WidgetSensitivePropertyInfo), '("spacing", BoxSpacingPropertyInfo), '("style", WidgetStylePropertyInfo), '("tooltip-markup", WidgetTooltipMarkupPropertyInfo), '("tooltip-text", WidgetTooltipTextPropertyInfo), '("valign", WidgetValignPropertyInfo), '("vexpand", WidgetVexpandPropertyInfo), '("vexpand-set", WidgetVexpandSetPropertyInfo), '("visible", WidgetVisiblePropertyInfo), '("width-request", WidgetWidthRequestPropertyInfo), '("window", WidgetWindowPropertyInfo)] :: [(Symbol, *)])

data ColorSelectionColorChangedSignalInfo
instance SignalInfo ColorSelectionColorChangedSignalInfo where
    type HaskellCallbackType ColorSelectionColorChangedSignalInfo = ColorSelectionColorChangedCallback
    connectSignal _ = connectColorSelectionColorChanged

type instance SignalList ColorSelection = ColorSelectionSignalList
type ColorSelectionSignalList = ('[ '("accel-closures-changed", WidgetAccelClosuresChangedSignalInfo), '("add", ContainerAddSignalInfo), '("button-press-event", WidgetButtonPressEventSignalInfo), '("button-release-event", WidgetButtonReleaseEventSignalInfo), '("can-activate-accel", WidgetCanActivateAccelSignalInfo), '("check-resize", ContainerCheckResizeSignalInfo), '("child-notify", WidgetChildNotifySignalInfo), '("color-changed", ColorSelectionColorChangedSignalInfo), '("composited-changed", WidgetCompositedChangedSignalInfo), '("configure-event", WidgetConfigureEventSignalInfo), '("damage-event", WidgetDamageEventSignalInfo), '("delete-event", WidgetDeleteEventSignalInfo), '("destroy", WidgetDestroySignalInfo), '("destroy-event", WidgetDestroyEventSignalInfo), '("direction-changed", WidgetDirectionChangedSignalInfo), '("drag-begin", WidgetDragBeginSignalInfo), '("drag-data-delete", WidgetDragDataDeleteSignalInfo), '("drag-data-get", WidgetDragDataGetSignalInfo), '("drag-data-received", WidgetDragDataReceivedSignalInfo), '("drag-drop", WidgetDragDropSignalInfo), '("drag-end", WidgetDragEndSignalInfo), '("drag-failed", WidgetDragFailedSignalInfo), '("drag-leave", WidgetDragLeaveSignalInfo), '("drag-motion", WidgetDragMotionSignalInfo), '("draw", WidgetDrawSignalInfo), '("enter-notify-event", WidgetEnterNotifyEventSignalInfo), '("event", WidgetEventSignalInfo), '("event-after", WidgetEventAfterSignalInfo), '("focus", WidgetFocusSignalInfo), '("focus-in-event", WidgetFocusInEventSignalInfo), '("focus-out-event", WidgetFocusOutEventSignalInfo), '("grab-broken-event", WidgetGrabBrokenEventSignalInfo), '("grab-focus", WidgetGrabFocusSignalInfo), '("grab-notify", WidgetGrabNotifySignalInfo), '("hide", WidgetHideSignalInfo), '("hierarchy-changed", WidgetHierarchyChangedSignalInfo), '("key-press-event", WidgetKeyPressEventSignalInfo), '("key-release-event", WidgetKeyReleaseEventSignalInfo), '("keynav-failed", WidgetKeynavFailedSignalInfo), '("leave-notify-event", WidgetLeaveNotifyEventSignalInfo), '("map", WidgetMapSignalInfo), '("map-event", WidgetMapEventSignalInfo), '("mnemonic-activate", WidgetMnemonicActivateSignalInfo), '("motion-notify-event", WidgetMotionNotifyEventSignalInfo), '("move-focus", WidgetMoveFocusSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("parent-set", WidgetParentSetSignalInfo), '("popup-menu", WidgetPopupMenuSignalInfo), '("property-notify-event", WidgetPropertyNotifyEventSignalInfo), '("proximity-in-event", WidgetProximityInEventSignalInfo), '("proximity-out-event", WidgetProximityOutEventSignalInfo), '("query-tooltip", WidgetQueryTooltipSignalInfo), '("realize", WidgetRealizeSignalInfo), '("remove", ContainerRemoveSignalInfo), '("screen-changed", WidgetScreenChangedSignalInfo), '("scroll-event", WidgetScrollEventSignalInfo), '("selection-clear-event", WidgetSelectionClearEventSignalInfo), '("selection-get", WidgetSelectionGetSignalInfo), '("selection-notify-event", WidgetSelectionNotifyEventSignalInfo), '("selection-received", WidgetSelectionReceivedSignalInfo), '("selection-request-event", WidgetSelectionRequestEventSignalInfo), '("set-focus-child", ContainerSetFocusChildSignalInfo), '("show", WidgetShowSignalInfo), '("show-help", WidgetShowHelpSignalInfo), '("size-allocate", WidgetSizeAllocateSignalInfo), '("state-changed", WidgetStateChangedSignalInfo), '("state-flags-changed", WidgetStateFlagsChangedSignalInfo), '("style-set", WidgetStyleSetSignalInfo), '("style-updated", WidgetStyleUpdatedSignalInfo), '("touch-event", WidgetTouchEventSignalInfo), '("unmap", WidgetUnmapSignalInfo), '("unmap-event", WidgetUnmapEventSignalInfo), '("unrealize", WidgetUnrealizeSignalInfo), '("visibility-notify-event", WidgetVisibilityNotifyEventSignalInfo), '("window-state-event", WidgetWindowStateEventSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method ColorSelection::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Gtk" "ColorSelection"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_new" gtk_color_selection_new :: 
    IO (Ptr ColorSelection)


colorSelectionNew ::
    (MonadIO m) =>
    m ColorSelection
colorSelectionNew  = liftIO $ do
    result <- gtk_color_selection_new
    checkUnexpectedReturnNULL "gtk_color_selection_new" result
    result' <- (newObject ColorSelection) result
    return result'

-- method ColorSelection::get_current_alpha
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt16
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_get_current_alpha" gtk_color_selection_get_current_alpha :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    IO Word16


colorSelectionGetCurrentAlpha ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m Word16
colorSelectionGetCurrentAlpha _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_color_selection_get_current_alpha _obj'
    touchManagedPtr _obj
    return result

-- method ColorSelection::get_current_color
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "color", argType = TInterface "Gdk" "Color", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_get_current_color" gtk_color_selection_get_current_color :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Ptr Gdk.Color ->                        -- color : TInterface "Gdk" "Color"
    IO ()

{-# DEPRECATED colorSelectionGetCurrentColor ["(Since version 3.4)","Use gtk_color_selection_get_current_rgba() instead."]#-}
colorSelectionGetCurrentColor ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m (Gdk.Color)
colorSelectionGetCurrentColor _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    color <- callocBoxedBytes 12 :: IO (Ptr Gdk.Color)
    gtk_color_selection_get_current_color _obj' color
    color' <- (wrapBoxed Gdk.Color) color
    touchManagedPtr _obj
    return color'

-- method ColorSelection::get_current_rgba
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "rgba", argType = TInterface "Gdk" "RGBA", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_get_current_rgba" gtk_color_selection_get_current_rgba :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Ptr Gdk.RGBA ->                         -- rgba : TInterface "Gdk" "RGBA"
    IO ()


colorSelectionGetCurrentRgba ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m (Gdk.RGBA)
colorSelectionGetCurrentRgba _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    rgba <- callocBoxedBytes 32 :: IO (Ptr Gdk.RGBA)
    gtk_color_selection_get_current_rgba _obj' rgba
    rgba' <- (wrapBoxed Gdk.RGBA) rgba
    touchManagedPtr _obj
    return rgba'

-- method ColorSelection::get_has_opacity_control
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_get_has_opacity_control" gtk_color_selection_get_has_opacity_control :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    IO CInt


colorSelectionGetHasOpacityControl ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m Bool
colorSelectionGetHasOpacityControl _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_color_selection_get_has_opacity_control _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method ColorSelection::get_has_palette
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_get_has_palette" gtk_color_selection_get_has_palette :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    IO CInt


colorSelectionGetHasPalette ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m Bool
colorSelectionGetHasPalette _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_color_selection_get_has_palette _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method ColorSelection::get_previous_alpha
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt16
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_get_previous_alpha" gtk_color_selection_get_previous_alpha :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    IO Word16


colorSelectionGetPreviousAlpha ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m Word16
colorSelectionGetPreviousAlpha _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_color_selection_get_previous_alpha _obj'
    touchManagedPtr _obj
    return result

-- method ColorSelection::get_previous_color
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "color", argType = TInterface "Gdk" "Color", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_get_previous_color" gtk_color_selection_get_previous_color :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Ptr Gdk.Color ->                        -- color : TInterface "Gdk" "Color"
    IO ()

{-# DEPRECATED colorSelectionGetPreviousColor ["(Since version 3.4)","Use gtk_color_selection_get_previous_rgba() instead."]#-}
colorSelectionGetPreviousColor ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m (Gdk.Color)
colorSelectionGetPreviousColor _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    color <- callocBoxedBytes 12 :: IO (Ptr Gdk.Color)
    gtk_color_selection_get_previous_color _obj' color
    color' <- (wrapBoxed Gdk.Color) color
    touchManagedPtr _obj
    return color'

-- method ColorSelection::get_previous_rgba
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "rgba", argType = TInterface "Gdk" "RGBA", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_get_previous_rgba" gtk_color_selection_get_previous_rgba :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Ptr Gdk.RGBA ->                         -- rgba : TInterface "Gdk" "RGBA"
    IO ()


colorSelectionGetPreviousRgba ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m (Gdk.RGBA)
colorSelectionGetPreviousRgba _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    rgba <- callocBoxedBytes 32 :: IO (Ptr Gdk.RGBA)
    gtk_color_selection_get_previous_rgba _obj' rgba
    rgba' <- (wrapBoxed Gdk.RGBA) rgba
    touchManagedPtr _obj
    return rgba'

-- method ColorSelection::is_adjusting
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_is_adjusting" gtk_color_selection_is_adjusting :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    IO CInt


colorSelectionIsAdjusting ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    m Bool
colorSelectionIsAdjusting _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    result <- gtk_color_selection_is_adjusting _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method ColorSelection::set_current_alpha
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "alpha", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "alpha", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_set_current_alpha" gtk_color_selection_set_current_alpha :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Word16 ->                               -- alpha : TBasicType TUInt16
    IO ()


colorSelectionSetCurrentAlpha ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    Word16 ->                               -- alpha
    m ()
colorSelectionSetCurrentAlpha _obj alpha = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_color_selection_set_current_alpha _obj' alpha
    touchManagedPtr _obj
    return ()

-- method ColorSelection::set_current_color
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "color", argType = TInterface "Gdk" "Color", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "color", argType = TInterface "Gdk" "Color", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_set_current_color" gtk_color_selection_set_current_color :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Ptr Gdk.Color ->                        -- color : TInterface "Gdk" "Color"
    IO ()

{-# DEPRECATED colorSelectionSetCurrentColor ["(Since version 3.4)","Use gtk_color_selection_set_current_rgba() instead."]#-}
colorSelectionSetCurrentColor ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    Gdk.Color ->                            -- color
    m ()
colorSelectionSetCurrentColor _obj color = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let color' = unsafeManagedPtrGetPtr color
    gtk_color_selection_set_current_color _obj' color'
    touchManagedPtr _obj
    touchManagedPtr color
    return ()

-- method ColorSelection::set_current_rgba
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "rgba", argType = TInterface "Gdk" "RGBA", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "rgba", argType = TInterface "Gdk" "RGBA", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_set_current_rgba" gtk_color_selection_set_current_rgba :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Ptr Gdk.RGBA ->                         -- rgba : TInterface "Gdk" "RGBA"
    IO ()


colorSelectionSetCurrentRgba ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    Gdk.RGBA ->                             -- rgba
    m ()
colorSelectionSetCurrentRgba _obj rgba = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let rgba' = unsafeManagedPtrGetPtr rgba
    gtk_color_selection_set_current_rgba _obj' rgba'
    touchManagedPtr _obj
    touchManagedPtr rgba
    return ()

-- method ColorSelection::set_has_opacity_control
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "has_opacity", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "has_opacity", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_set_has_opacity_control" gtk_color_selection_set_has_opacity_control :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    CInt ->                                 -- has_opacity : TBasicType TBoolean
    IO ()


colorSelectionSetHasOpacityControl ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- has_opacity
    m ()
colorSelectionSetHasOpacityControl _obj has_opacity = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let has_opacity' = (fromIntegral . fromEnum) has_opacity
    gtk_color_selection_set_has_opacity_control _obj' has_opacity'
    touchManagedPtr _obj
    return ()

-- method ColorSelection::set_has_palette
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "has_palette", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "has_palette", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_set_has_palette" gtk_color_selection_set_has_palette :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    CInt ->                                 -- has_palette : TBasicType TBoolean
    IO ()


colorSelectionSetHasPalette ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    Bool ->                                 -- has_palette
    m ()
colorSelectionSetHasPalette _obj has_palette = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let has_palette' = (fromIntegral . fromEnum) has_palette
    gtk_color_selection_set_has_palette _obj' has_palette'
    touchManagedPtr _obj
    return ()

-- method ColorSelection::set_previous_alpha
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "alpha", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "alpha", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_set_previous_alpha" gtk_color_selection_set_previous_alpha :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Word16 ->                               -- alpha : TBasicType TUInt16
    IO ()


colorSelectionSetPreviousAlpha ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    Word16 ->                               -- alpha
    m ()
colorSelectionSetPreviousAlpha _obj alpha = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    gtk_color_selection_set_previous_alpha _obj' alpha
    touchManagedPtr _obj
    return ()

-- method ColorSelection::set_previous_color
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "color", argType = TInterface "Gdk" "Color", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "color", argType = TInterface "Gdk" "Color", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_set_previous_color" gtk_color_selection_set_previous_color :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Ptr Gdk.Color ->                        -- color : TInterface "Gdk" "Color"
    IO ()

{-# DEPRECATED colorSelectionSetPreviousColor ["(Since version 3.4)","Use gtk_color_selection_set_previous_rgba() instead."]#-}
colorSelectionSetPreviousColor ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    Gdk.Color ->                            -- color
    m ()
colorSelectionSetPreviousColor _obj color = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let color' = unsafeManagedPtrGetPtr color
    gtk_color_selection_set_previous_color _obj' color'
    touchManagedPtr _obj
    touchManagedPtr color
    return ()

-- method ColorSelection::set_previous_rgba
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "rgba", argType = TInterface "Gdk" "RGBA", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "ColorSelection", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "rgba", argType = TInterface "Gdk" "RGBA", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_set_previous_rgba" gtk_color_selection_set_previous_rgba :: 
    Ptr ColorSelection ->                   -- _obj : TInterface "Gtk" "ColorSelection"
    Ptr Gdk.RGBA ->                         -- rgba : TInterface "Gdk" "RGBA"
    IO ()


colorSelectionSetPreviousRgba ::
    (MonadIO m, ColorSelectionK a) =>
    a ->                                    -- _obj
    Gdk.RGBA ->                             -- rgba
    m ()
colorSelectionSetPreviousRgba _obj rgba = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    let rgba' = unsafeManagedPtrGetPtr rgba
    gtk_color_selection_set_previous_rgba _obj' rgba'
    touchManagedPtr _obj
    touchManagedPtr rgba
    return ()

-- method ColorSelection::palette_from_string
-- method type : MemberFunction
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "colors", argType = TCArray False (-1) 2 (TInterface "Gdk" "Color"), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "n_colors", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : [Arg {argName = "n_colors", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_palette_from_string" gtk_color_selection_palette_from_string :: 
    CString ->                              -- str : TBasicType TUTF8
    Ptr (Ptr Gdk.Color) ->                  -- colors : TCArray False (-1) 2 (TInterface "Gdk" "Color")
    Ptr Int32 ->                            -- n_colors : TBasicType TInt32
    IO CInt


colorSelectionPaletteFromString ::
    (MonadIO m) =>
    T.Text ->                               -- str
    m (Bool,[Gdk.Color])
colorSelectionPaletteFromString str = liftIO $ do
    str' <- textToCString str
    colors <- allocMem :: IO (Ptr (Ptr Gdk.Color))
    n_colors <- allocMem :: IO (Ptr Int32)
    result <- gtk_color_selection_palette_from_string str' colors n_colors
    n_colors' <- peek n_colors
    let result' = (/= 0) result
    colors' <- peek colors
    colors'' <- (unpackBoxedArrayWithLength 12 n_colors') colors'
    colors''' <- mapM (wrapBoxed Gdk.Color) colors''
    freeMem colors'
    freeMem str'
    freeMem colors
    freeMem n_colors
    return (result', colors''')

-- method ColorSelection::palette_to_string
-- method type : MemberFunction
-- Args : [Arg {argName = "colors", argType = TCArray False (-1) 1 (TInterface "Gdk" "Color"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n_colors", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "n_colors", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "colors", argType = TCArray False (-1) 1 (TInterface "Gdk" "Color"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "gtk_color_selection_palette_to_string" gtk_color_selection_palette_to_string :: 
    Ptr Gdk.Color ->                        -- colors : TCArray False (-1) 1 (TInterface "Gdk" "Color")
    Int32 ->                                -- n_colors : TBasicType TInt32
    IO CString


colorSelectionPaletteToString ::
    (MonadIO m) =>
    [Gdk.Color] ->                          -- colors
    m T.Text
colorSelectionPaletteToString colors = liftIO $ do
    let n_colors = fromIntegral $ length colors
    let colors' = map unsafeManagedPtrGetPtr colors
    colors'' <- packBlockArray 12 colors'
    result <- gtk_color_selection_palette_to_string colors'' n_colors
    checkUnexpectedReturnNULL "gtk_color_selection_palette_to_string" result
    result' <- cstringToText result
    freeMem result
    mapM_ touchManagedPtr colors
    freeMem colors''
    return result'