{-# 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 :: forall icon. IconClass icon => icon -> IO Emblem
emblemNew icon
icon =
    (ForeignPtr Emblem -> Emblem, FinalizerPtr Emblem)
-> IO (Ptr Emblem) -> IO Emblem
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr Emblem -> Emblem, FinalizerPtr Emblem)
forall {a}. (ForeignPtr Emblem -> Emblem, FinalizerPtr a)
mkEmblem (IO (Ptr Emblem) -> IO Emblem) -> IO (Ptr Emblem) -> IO Emblem
forall a b. (a -> b) -> a -> b
$
    (\(Icon ForeignPtr Icon
arg1) -> ForeignPtr Icon -> (Ptr Icon -> IO (Ptr Emblem)) -> IO (Ptr Emblem)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Icon
arg1 ((Ptr Icon -> IO (Ptr Emblem)) -> IO (Ptr Emblem))
-> (Ptr Icon -> IO (Ptr Emblem)) -> IO (Ptr Emblem)
forall a b. (a -> b) -> a -> b
$ \Ptr Icon
argPtr1 ->Ptr Icon -> IO (Ptr Emblem)
g_emblem_new Ptr Icon
argPtr1) (icon -> Icon
forall o. IconClass o => o -> Icon
toIcon icon
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 :: forall icon. IconClass icon => icon -> EmblemOrigin -> IO Emblem
emblemNewWithOrigin icon
icon EmblemOrigin
origin =
    (ForeignPtr Emblem -> Emblem, FinalizerPtr Emblem)
-> IO (Ptr Emblem) -> IO Emblem
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr Emblem -> Emblem, FinalizerPtr Emblem)
forall {a}. (ForeignPtr Emblem -> Emblem, FinalizerPtr a)
mkEmblem (IO (Ptr Emblem) -> IO Emblem) -> IO (Ptr Emblem) -> IO Emblem
forall a b. (a -> b) -> a -> b
$
    (\(Icon ForeignPtr Icon
arg1) CInt
arg2 -> ForeignPtr Icon -> (Ptr Icon -> IO (Ptr Emblem)) -> IO (Ptr Emblem)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Icon
arg1 ((Ptr Icon -> IO (Ptr Emblem)) -> IO (Ptr Emblem))
-> (Ptr Icon -> IO (Ptr Emblem)) -> IO (Ptr Emblem)
forall a b. (a -> b) -> a -> b
$ \Ptr Icon
argPtr1 ->Ptr Icon -> CInt -> IO (Ptr Emblem)
g_emblem_new_with_origin Ptr Icon
argPtr1 CInt
arg2) (icon -> Icon
forall o. IconClass o => o -> Icon
toIcon icon
icon) ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EmblemOrigin -> Int) -> EmblemOrigin -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EmblemOrigin -> Int
forall a. Enum a => a -> Int
fromEnum) EmblemOrigin
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 :: forall emblem. EmblemClass emblem => emblem -> IO Icon
emblemGetIcon emblem
emblem =
    (ForeignPtr Icon -> Icon, FinalizerPtr Icon)
-> IO (Ptr Icon) -> IO Icon
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewGObject (ForeignPtr Icon -> Icon, FinalizerPtr Icon)
forall {a}. (ForeignPtr Icon -> Icon, FinalizerPtr a)
mkIcon (IO (Ptr Icon) -> IO Icon) -> IO (Ptr Icon) -> IO Icon
forall a b. (a -> b) -> a -> b
$
    (\(Emblem ForeignPtr Emblem
arg1) -> ForeignPtr Emblem -> (Ptr Emblem -> IO (Ptr Icon)) -> IO (Ptr Icon)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Emblem
arg1 ((Ptr Emblem -> IO (Ptr Icon)) -> IO (Ptr Icon))
-> (Ptr Emblem -> IO (Ptr Icon)) -> IO (Ptr Icon)
forall a b. (a -> b) -> a -> b
$ \Ptr Emblem
argPtr1 ->Ptr Emblem -> IO (Ptr Icon)
g_emblem_get_icon Ptr Emblem
argPtr1) (emblem -> Emblem
forall o. EmblemClass o => o -> Emblem
toEmblem emblem
emblem)

-- | Gets the origin of the emblem.
emblemGetOrigin :: EmblemClass emblem => emblem
 -> IO EmblemOrigin
emblemGetOrigin :: forall emblem. EmblemClass emblem => emblem -> IO EmblemOrigin
emblemGetOrigin emblem
emblem =
  (CInt -> EmblemOrigin) -> IO CInt -> IO EmblemOrigin
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int -> EmblemOrigin
forall a. Enum a => Int -> a
toEnum (Int -> EmblemOrigin) -> (CInt -> Int) -> CInt -> EmblemOrigin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (IO CInt -> IO EmblemOrigin) -> IO CInt -> IO EmblemOrigin
forall a b. (a -> b) -> a -> b
$
  (\(Emblem ForeignPtr Emblem
arg1) -> ForeignPtr Emblem -> (Ptr Emblem -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Emblem
arg1 ((Ptr Emblem -> IO CInt) -> IO CInt)
-> (Ptr Emblem -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr Emblem
argPtr1 ->Ptr Emblem -> IO CInt
g_emblem_get_origin Ptr Emblem
argPtr1) (emblem -> Emblem
forall o. EmblemClass o => o -> Emblem
toEmblem emblem
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))