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

The #PangoColor structure is used to
represent a color in an uncalibrated RGB color-space.
-}

module GI.Pango.Structs.Color
    ( 

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


 -- * Methods
-- ** colorCopy
    colorCopy                               ,


-- ** colorFree
    colorFree                               ,


-- ** colorParse
    colorParse                              ,


-- ** colorToString
    colorToString                           ,




 -- * Properties
-- ** Blue
    colorReadBlue                           ,


-- ** Green
    colorReadGreen                          ,


-- ** Red
    colorReadRed                            ,




    ) 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.Pango.Types
import GI.Pango.Callbacks

newtype Color = Color (ForeignPtr Color)
foreign import ccall "pango_color_get_type" c_pango_color_get_type :: 
    IO GType

instance BoxedObject Color where
    boxedType _ = c_pango_color_get_type

noColor :: Maybe Color
noColor = Nothing

colorReadRed :: Color -> IO Word16
colorReadRed s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Word16
    return val

colorReadGreen :: Color -> IO Word16
colorReadGreen s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 2) :: IO Word16
    return val

colorReadBlue :: Color -> IO Word16
colorReadBlue s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO Word16
    return val

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

foreign import ccall "pango_color_copy" pango_color_copy :: 
    Ptr Color ->                            -- _obj : TInterface "Pango" "Color"
    IO (Ptr Color)


colorCopy ::
    (MonadIO m) =>
    Color ->                                -- _obj
    m Color
colorCopy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- pango_color_copy _obj'
    checkUnexpectedReturnNULL "pango_color_copy" result
    result' <- (wrapBoxed Color) result
    touchManagedPtr _obj
    return result'

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

foreign import ccall "pango_color_free" pango_color_free :: 
    Ptr Color ->                            -- _obj : TInterface "Pango" "Color"
    IO ()


colorFree ::
    (MonadIO m) =>
    Color ->                                -- _obj
    m ()
colorFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    pango_color_free _obj'
    touchManagedPtr _obj
    return ()

-- method Color::parse
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Color", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "spec", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Color", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "spec", 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 "pango_color_parse" pango_color_parse :: 
    Ptr Color ->                            -- _obj : TInterface "Pango" "Color"
    CString ->                              -- spec : TBasicType TUTF8
    IO CInt


colorParse ::
    (MonadIO m) =>
    Color ->                                -- _obj
    T.Text ->                               -- spec
    m Bool
colorParse _obj spec = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    spec' <- textToCString spec
    result <- pango_color_parse _obj' spec'
    let result' = (/= 0) result
    touchManagedPtr _obj
    freeMem spec'
    return result'

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

foreign import ccall "pango_color_to_string" pango_color_to_string :: 
    Ptr Color ->                            -- _obj : TInterface "Pango" "Color"
    IO CString


colorToString ::
    (MonadIO m) =>
    Color ->                                -- _obj
    m T.Text
colorToString _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- pango_color_to_string _obj'
    checkUnexpectedReturnNULL "pango_color_to_string" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr _obj
    return result'