{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gdk.Structs.Color.Color' is used to describe a color,
-- similar to the XColor struct used in the X11 drawing API.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gdk.Structs.Color
    ( 

-- * Exported types
    Color(..)                               ,
    newZeroColor                            ,
    noColor                                 ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveColorMethod                      ,
#endif


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    ColorCopyMethodInfo                     ,
#endif
    colorCopy                               ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    ColorEqualMethodInfo                    ,
#endif
    colorEqual                              ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    ColorFreeMethodInfo                     ,
#endif
    colorFree                               ,


-- ** hash #method:hash#

#if defined(ENABLE_OVERLOADING)
    ColorHashMethodInfo                     ,
#endif
    colorHash                               ,


-- ** parse #method:parse#

    colorParse                              ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    ColorToStringMethodInfo                 ,
#endif
    colorToString                           ,




 -- * Properties
-- ** blue #attr:blue#
-- | The blue component of the color

#if defined(ENABLE_OVERLOADING)
    color_blue                              ,
#endif
    getColorBlue                            ,
    setColorBlue                            ,


-- ** green #attr:green#
-- | The green component of the color

#if defined(ENABLE_OVERLOADING)
    color_green                             ,
#endif
    getColorGreen                           ,
    setColorGreen                           ,


-- ** pixel #attr:pixel#
-- | For allocated colors, the pixel value used to
--     draw this color on the screen. Not used anymore.

#if defined(ENABLE_OVERLOADING)
    color_pixel                             ,
#endif
    getColorPixel                           ,
    setColorPixel                           ,


-- ** red #attr:red#
-- | The red component of the color. This is
--     a value between 0 and 65535, with 65535 indicating
--     full intensity

#if defined(ENABLE_OVERLOADING)
    color_red                               ,
#endif
    getColorRed                             ,
    setColorRed                             ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL


-- | Memory-managed wrapper type.
newtype Color = Color (ManagedPtr Color)
    deriving (Color -> Color -> Bool
(Color -> Color -> Bool) -> (Color -> Color -> Bool) -> Eq Color
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c== :: Color -> Color -> Bool
Eq)
foreign import ccall "gdk_color_get_type" c_gdk_color_get_type :: 
    IO GType

instance BoxedObject Color where
    boxedType :: Color -> IO GType
boxedType _ = IO GType
c_gdk_color_get_type

-- | Convert 'Color' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Color where
    toGValue :: Color -> IO GValue
toGValue o :: Color
o = do
        GType
gtype <- IO GType
c_gdk_color_get_type
        Color -> (Ptr Color -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Color
o (GType -> (GValue -> Ptr Color -> IO ()) -> Ptr Color -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Color -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO Color
fromGValue gv :: GValue
gv = do
        Ptr Color
ptr <- GValue -> IO (Ptr Color)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Color)
        (ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Color -> Color
Color Ptr Color
ptr
        
    

-- | Construct a `Color` struct initialized to zero.
newZeroColor :: MonadIO m => m Color
newZeroColor :: m Color
newZeroColor = IO Color -> m Color
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Color -> m Color) -> IO Color -> m Color
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Color)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 12 IO (Ptr Color) -> (Ptr Color -> IO Color) -> IO Color
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Color -> Color
Color

instance tag ~ 'AttrSet => Constructible Color tag where
    new :: (ManagedPtr Color -> Color) -> [AttrOp Color tag] -> m Color
new _ attrs :: [AttrOp Color tag]
attrs = do
        Color
o <- m Color
forall (m :: * -> *). MonadIO m => m Color
newZeroColor
        Color -> [AttrOp Color 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Color
o [AttrOp Color tag]
[AttrOp Color 'AttrSet]
attrs
        Color -> m Color
forall (m :: * -> *) a. Monad m => a -> m a
return Color
o


-- | A convenience alias for `Nothing` :: `Maybe` `Color`.
noColor :: Maybe Color
noColor :: Maybe Color
noColor = Maybe Color
forall a. Maybe a
Nothing

-- | Get the value of the “@pixel@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' color #pixel
-- @
getColorPixel :: MonadIO m => Color -> m Word32
getColorPixel :: Color -> m Word32
getColorPixel s :: Color
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Color
s ((Ptr Color -> IO Word32) -> IO Word32)
-> (Ptr Color -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Color
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Color
ptr Ptr Color -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@pixel@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' color [ #pixel 'Data.GI.Base.Attributes.:=' value ]
-- @
setColorPixel :: MonadIO m => Color -> Word32 -> m ()
setColorPixel :: Color -> Word32 -> m ()
setColorPixel s :: Color
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Color
s ((Ptr Color -> IO ()) -> IO ()) -> (Ptr Color -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Color
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Color
ptr Ptr Color -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data ColorPixelFieldInfo
instance AttrInfo ColorPixelFieldInfo where
    type AttrBaseTypeConstraint ColorPixelFieldInfo = (~) Color
    type AttrAllowedOps ColorPixelFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ColorPixelFieldInfo = (~) Word32
    type AttrTransferTypeConstraint ColorPixelFieldInfo = (~)Word32
    type AttrTransferType ColorPixelFieldInfo = Word32
    type AttrGetType ColorPixelFieldInfo = Word32
    type AttrLabel ColorPixelFieldInfo = "pixel"
    type AttrOrigin ColorPixelFieldInfo = Color
    attrGet = getColorPixel
    attrSet = setColorPixel
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

color_pixel :: AttrLabelProxy "pixel"
color_pixel = AttrLabelProxy

#endif


-- | Get the value of the “@red@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' color #red
-- @
getColorRed :: MonadIO m => Color -> m Word16
getColorRed :: Color -> m Word16
getColorRed s :: Color
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Color
s ((Ptr Color -> IO Word16) -> IO Word16)
-> (Ptr Color -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Color
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr Color
ptr Ptr Color -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4) :: IO Word16
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@red@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' color [ #red 'Data.GI.Base.Attributes.:=' value ]
-- @
setColorRed :: MonadIO m => Color -> Word16 -> m ()
setColorRed :: Color -> Word16 -> m ()
setColorRed s :: Color
s val :: Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Color
s ((Ptr Color -> IO ()) -> IO ()) -> (Ptr Color -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Color
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Color
ptr Ptr Color -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data ColorRedFieldInfo
instance AttrInfo ColorRedFieldInfo where
    type AttrBaseTypeConstraint ColorRedFieldInfo = (~) Color
    type AttrAllowedOps ColorRedFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ColorRedFieldInfo = (~) Word16
    type AttrTransferTypeConstraint ColorRedFieldInfo = (~)Word16
    type AttrTransferType ColorRedFieldInfo = Word16
    type AttrGetType ColorRedFieldInfo = Word16
    type AttrLabel ColorRedFieldInfo = "red"
    type AttrOrigin ColorRedFieldInfo = Color
    attrGet = getColorRed
    attrSet = setColorRed
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

color_red :: AttrLabelProxy "red"
color_red = AttrLabelProxy

#endif


-- | Get the value of the “@green@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' color #green
-- @
getColorGreen :: MonadIO m => Color -> m Word16
getColorGreen :: Color -> m Word16
getColorGreen s :: Color
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Color
s ((Ptr Color -> IO Word16) -> IO Word16)
-> (Ptr Color -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Color
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr Color
ptr Ptr Color -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 6) :: IO Word16
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@green@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' color [ #green 'Data.GI.Base.Attributes.:=' value ]
-- @
setColorGreen :: MonadIO m => Color -> Word16 -> m ()
setColorGreen :: Color -> Word16 -> m ()
setColorGreen s :: Color
s val :: Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Color
s ((Ptr Color -> IO ()) -> IO ()) -> (Ptr Color -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Color
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Color
ptr Ptr Color -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 6) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data ColorGreenFieldInfo
instance AttrInfo ColorGreenFieldInfo where
    type AttrBaseTypeConstraint ColorGreenFieldInfo = (~) Color
    type AttrAllowedOps ColorGreenFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ColorGreenFieldInfo = (~) Word16
    type AttrTransferTypeConstraint ColorGreenFieldInfo = (~)Word16
    type AttrTransferType ColorGreenFieldInfo = Word16
    type AttrGetType ColorGreenFieldInfo = Word16
    type AttrLabel ColorGreenFieldInfo = "green"
    type AttrOrigin ColorGreenFieldInfo = Color
    attrGet = getColorGreen
    attrSet = setColorGreen
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

color_green :: AttrLabelProxy "green"
color_green = AttrLabelProxy

#endif


-- | Get the value of the “@blue@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' color #blue
-- @
getColorBlue :: MonadIO m => Color -> m Word16
getColorBlue :: Color -> m Word16
getColorBlue s :: Color
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Color
s ((Ptr Color -> IO Word16) -> IO Word16)
-> (Ptr Color -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Color
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr Color
ptr Ptr Color -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO Word16
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
val

-- | Set the value of the “@blue@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' color [ #blue 'Data.GI.Base.Attributes.:=' value ]
-- @
setColorBlue :: MonadIO m => Color -> Word16 -> m ()
setColorBlue :: Color -> Word16 -> m ()
setColorBlue s :: Color
s val :: Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Color -> (Ptr Color -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Color
s ((Ptr Color -> IO ()) -> IO ()) -> (Ptr Color -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Color
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Color
ptr Ptr Color -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Word16
val :: Word16)

#if defined(ENABLE_OVERLOADING)
data ColorBlueFieldInfo
instance AttrInfo ColorBlueFieldInfo where
    type AttrBaseTypeConstraint ColorBlueFieldInfo = (~) Color
    type AttrAllowedOps ColorBlueFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ColorBlueFieldInfo = (~) Word16
    type AttrTransferTypeConstraint ColorBlueFieldInfo = (~)Word16
    type AttrTransferType ColorBlueFieldInfo = Word16
    type AttrGetType ColorBlueFieldInfo = Word16
    type AttrLabel ColorBlueFieldInfo = "blue"
    type AttrOrigin ColorBlueFieldInfo = Color
    attrGet = getColorBlue
    attrSet = setColorBlue
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

color_blue :: AttrLabelProxy "blue"
color_blue = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Color
type instance O.AttributeList Color = ColorAttributeList
type ColorAttributeList = ('[ '("pixel", ColorPixelFieldInfo), '("red", ColorRedFieldInfo), '("green", ColorGreenFieldInfo), '("blue", ColorBlueFieldInfo)] :: [(Symbol, *)])
#endif

-- method Color::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkColor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Color" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_color_copy" gdk_color_copy :: 
    Ptr Color ->                            -- color : TInterface (Name {namespace = "Gdk", name = "Color"})
    IO (Ptr Color)

{-# DEPRECATED colorCopy ["(Since version 3.14)","Use t'GI.Gdk.Structs.RGBA.RGBA'"] #-}
-- | Makes a copy of a t'GI.Gdk.Structs.Color.Color'.
-- 
-- The result must be freed using 'GI.Gdk.Structs.Color.colorFree'.
colorCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Color
    -- ^ /@color@/: a t'GI.Gdk.Structs.Color.Color'
    -> m Color
    -- ^ __Returns:__ a copy of /@color@/
colorCopy :: Color -> m Color
colorCopy color :: Color
color = IO Color -> m Color
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Color -> m Color) -> IO Color -> m Color
forall a b. (a -> b) -> a -> b
$ do
    Ptr Color
color' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
color
    Ptr Color
result <- Ptr Color -> IO (Ptr Color)
gdk_color_copy Ptr Color
color'
    Text -> Ptr Color -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "colorCopy" Ptr Color
result
    Color
result' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Color -> Color
Color) Ptr Color
result
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
color
    Color -> IO Color
forall (m :: * -> *) a. Monad m => a -> m a
return Color
result'

#if defined(ENABLE_OVERLOADING)
data ColorCopyMethodInfo
instance (signature ~ (m Color), MonadIO m) => O.MethodInfo ColorCopyMethodInfo Color signature where
    overloadedMethod = colorCopy

#endif

-- method Color::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "colora"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkColor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "colorb"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GdkColor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_color_equal" gdk_color_equal :: 
    Ptr Color ->                            -- colora : TInterface (Name {namespace = "Gdk", name = "Color"})
    Ptr Color ->                            -- colorb : TInterface (Name {namespace = "Gdk", name = "Color"})
    IO CInt

{-# DEPRECATED colorEqual ["(Since version 3.14)","Use t'GI.Gdk.Structs.RGBA.RGBA'"] #-}
-- | Compares two colors.
colorEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Color
    -- ^ /@colora@/: a t'GI.Gdk.Structs.Color.Color'
    -> Color
    -- ^ /@colorb@/: another t'GI.Gdk.Structs.Color.Color'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the two colors compare equal
colorEqual :: Color -> Color -> m Bool
colorEqual colora :: Color
colora colorb :: Color
colorb = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Color
colora' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
colora
    Ptr Color
colorb' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
colorb
    CInt
result <- Ptr Color -> Ptr Color -> IO CInt
gdk_color_equal Ptr Color
colora' Ptr Color
colorb'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
colora
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
colorb
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ColorEqualMethodInfo
instance (signature ~ (Color -> m Bool), MonadIO m) => O.MethodInfo ColorEqualMethodInfo Color signature where
    overloadedMethod = colorEqual

#endif

-- method Color::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkColor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_color_free" gdk_color_free :: 
    Ptr Color ->                            -- color : TInterface (Name {namespace = "Gdk", name = "Color"})
    IO ()

{-# DEPRECATED colorFree ["(Since version 3.14)","Use t'GI.Gdk.Structs.RGBA.RGBA'"] #-}
-- | Frees a t'GI.Gdk.Structs.Color.Color' created with 'GI.Gdk.Structs.Color.colorCopy'.
colorFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Color
    -- ^ /@color@/: a t'GI.Gdk.Structs.Color.Color'
    -> m ()
colorFree :: Color -> m ()
colorFree color :: Color
color = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Color
color' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
color
    Ptr Color -> IO ()
gdk_color_free Ptr Color
color'
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
color
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ColorFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ColorFreeMethodInfo Color signature where
    overloadedMethod = colorFree

#endif

-- method Color::hash
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkColor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_color_hash" gdk_color_hash :: 
    Ptr Color ->                            -- color : TInterface (Name {namespace = "Gdk", name = "Color"})
    IO Word32

{-# DEPRECATED colorHash ["(Since version 3.14)","Use t'GI.Gdk.Structs.RGBA.RGBA'"] #-}
-- | A hash function suitable for using for a hash
-- table that stores @/GdkColors/@.
colorHash ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Color
    -- ^ /@color@/: a t'GI.Gdk.Structs.Color.Color'
    -> m Word32
    -- ^ __Returns:__ The hash function applied to /@color@/
colorHash :: Color -> m Word32
colorHash color :: Color
color = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Color
color' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
color
    Word32
result <- Ptr Color -> IO Word32
gdk_color_hash Ptr Color
color'
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
color
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data ColorHashMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ColorHashMethodInfo Color signature where
    overloadedMethod = colorHash

#endif

-- method Color::to_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkColor" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_color_to_string" gdk_color_to_string :: 
    Ptr Color ->                            -- color : TInterface (Name {namespace = "Gdk", name = "Color"})
    IO CString

{-# DEPRECATED colorToString ["(Since version 3.14)","Use t'GI.Gdk.Structs.RGBA.RGBA'"] #-}
-- | Returns a textual specification of /@color@/ in the hexadecimal
-- form “#rrrrggggbbbb” where “r”, “g” and “b” are hex digits
-- representing the red, green and blue components respectively.
-- 
-- The returned string can be parsed by 'GI.Gdk.Functions.colorParse'.
-- 
-- /Since: 2.12/
colorToString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Color
    -- ^ /@color@/: a t'GI.Gdk.Structs.Color.Color'
    -> m T.Text
    -- ^ __Returns:__ a newly-allocated text string
colorToString :: Color -> m Text
colorToString color :: Color
color = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Color
color' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
color
    CString
result <- Ptr Color -> IO CString
gdk_color_to_string Ptr Color
color'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "colorToString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Color
color
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ColorToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo ColorToStringMethodInfo Color signature where
    overloadedMethod = colorToString

#endif

-- method Color::parse
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "spec"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string specifying the color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Color" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GdkColor to fill in"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_color_parse" gdk_color_parse :: 
    CString ->                              -- spec : TBasicType TUTF8
    Ptr Color ->                            -- color : TInterface (Name {namespace = "Gdk", name = "Color"})
    IO CInt

{-# DEPRECATED colorParse ["(Since version 3.14)","Use t'GI.Gdk.Structs.RGBA.RGBA'"] #-}
-- | Parses a textual specification of a color and fill in the
-- /@red@/, /@green@/, and /@blue@/ fields of a t'GI.Gdk.Structs.Color.Color'.
-- 
-- The string can either one of a large set of standard names
-- (taken from the X11 @rgb.txt@ file), or it can be a hexadecimal
-- value in the form “#rgb” “#rrggbb”, “#rrrgggbbb” or
-- “#rrrrggggbbbb” where “r”, “g” and “b” are hex digits of
-- the red, green, and blue components of the color, respectively.
-- (White in the four forms is “#fff”, “#ffffff”, “#fffffffff”
-- and “#ffffffffffff”).
colorParse ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@spec@/: the string specifying the color
    -> m ((Bool, Color))
    -- ^ __Returns:__ 'P.True' if the parsing succeeded
colorParse :: Text -> m (Bool, Color)
colorParse spec :: Text
spec = IO (Bool, Color) -> m (Bool, Color)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Color) -> m (Bool, Color))
-> IO (Bool, Color) -> m (Bool, Color)
forall a b. (a -> b) -> a -> b
$ do
    CString
spec' <- Text -> IO CString
textToCString Text
spec
    Ptr Color
color <- Int -> IO (Ptr Color)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 12 :: IO (Ptr Color)
    CInt
result <- CString -> Ptr Color -> IO CInt
gdk_color_parse CString
spec' Ptr Color
color
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Color
color' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Color -> Color
Color) Ptr Color
color
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
spec'
    (Bool, Color) -> IO (Bool, Color)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Color
color')

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveColorMethod (t :: Symbol) (o :: *) :: * where
    ResolveColorMethod "copy" o = ColorCopyMethodInfo
    ResolveColorMethod "equal" o = ColorEqualMethodInfo
    ResolveColorMethod "free" o = ColorFreeMethodInfo
    ResolveColorMethod "hash" o = ColorHashMethodInfo
    ResolveColorMethod "toString" o = ColorToStringMethodInfo
    ResolveColorMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveColorMethod t Color, O.MethodInfo info Color p) => OL.IsLabel t (Color -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif