{-# LINE 2 "./System/GIO/Icons/Emblem.chs" #-}
-- GIMP Toolkit (GTK) Binding for Haskell: binding to gio -*-haskell-*-
--
-- Author : Andy Stewart
-- Created: 30-Apirl-2010
--
-- Copyright (c) 2010 Andy Stewart
--
-- This library is free software: you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public License
-- as published by the Free Software Foundation, either version 3 of
-- the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- Lesser General Public License for more details.
--
-- You should have received a copy of the GNU Lesser General Public
-- License along with this program. If not, see
-- <http:
--
-- GIO, the C library which this Haskell library depends on, is
-- available under LGPL Version 2. The documentation included with
-- this library is based on the original GIO documentation.
--
-- | Maintainer : gtk2hs-devel@lists.sourceforge.net
-- Stability : alpha
-- Portability : portable (depends on GHC)
module System.GIO.Icons.Emblem (
-- * Details
--
-- | 'Emblem' is an implementation of 'Icon' that supports having an emblem, which is an icon with
-- additional properties. It can than be added to a 'EmblemedIcon'.
--
-- Currently, only metainformation about the emblem's origin is supported. More may be added in the
-- future.


-- * Types
    Emblem(..),
    EmblemClass,

-- * Enums
    EmblemOrigin (..),

-- * Methods
    emblemNew,
    emblemNewWithOrigin,
    emblemGetIcon,
    emblemGetOrigin,

    ) where

import Control.Monad
import System.GIO.Enums
import System.Glib.FFI
import System.Glib.Flags
import System.Glib.GError
import System.Glib.GObject
import System.Glib.UTFString
import System.GIO.Types
{-# LINE 63 "./System/GIO/Icons/Emblem.chs" #-}


{-# LINE 65 "./System/GIO/Icons/Emblem.chs" #-}


-------------------
-- Methods
-- | Creates a new emblem for icon.
emblemNew :: IconClass icon => icon -> IO Emblem
emblemNew icon =
    wrapNewGObject mkEmblem $
    (\(Icon arg1) -> withForeignPtr arg1 $ \argPtr1 ->g_emblem_new argPtr1) (toIcon icon)

-- | Creates a new emblem for icon.
emblemNewWithOrigin :: IconClass icon
 => icon -- ^ @icon@ a 'Icon' containing the icon.
 -> EmblemOrigin -- ^ @origin@ a 'EmblemOrigin' enum defining the emblem's origin 
 -> IO Emblem
emblemNewWithOrigin icon origin =
    wrapNewGObject mkEmblem $
    (\(Icon arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->g_emblem_new_with_origin argPtr1 arg2) (toIcon icon) ((fromIntegral . fromEnum) origin)

-- | Gives back the icon from emblem.
emblemGetIcon :: EmblemClass emblem
 => emblem -- ^ @emblem@ a 'Emblem' from which the icon should be extracted.
 -> IO Icon -- ^ returns a 'Icon'. The returned object belongs to the emblem and should not be modified or freed.
emblemGetIcon emblem =
    makeNewGObject mkIcon $
    (\(Emblem arg1) -> withForeignPtr arg1 $ \argPtr1 ->g_emblem_get_icon argPtr1) (toEmblem emblem)

-- | Gets the origin of the emblem.
emblemGetOrigin :: EmblemClass emblem => emblem
 -> IO EmblemOrigin
emblemGetOrigin emblem =
  liftM (toEnum . fromIntegral) $
  (\(Emblem arg1) -> withForeignPtr arg1 $ \argPtr1 ->g_emblem_get_origin argPtr1) (toEmblem emblem)

foreign import ccall safe "g_emblem_new"
  g_emblem_new :: ((Ptr Icon) -> (IO (Ptr Emblem)))

foreign import ccall safe "g_emblem_new_with_origin"
  g_emblem_new_with_origin :: ((Ptr Icon) -> (CInt -> (IO (Ptr Emblem))))

foreign import ccall safe "g_emblem_get_icon"
  g_emblem_get_icon :: ((Ptr Emblem) -> (IO (Ptr Icon)))

foreign import ccall safe "g_emblem_get_origin"
  g_emblem_get_origin :: ((Ptr Emblem) -> (IO CInt))