{-# LINE 2 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}
-- -*-haskell-*-
-- GIMP Toolkit (GTK) IconFactory
--
-- Author : Axel Simon
--
-- Created: 24 May 2001
--
-- Copyright (C) 1999-2005 Axel Simon
--
-- 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 2.1 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.
--
-- |
-- Maintainer : gtk2hs-users@lists.sourceforge.net
-- Stability : provisional
-- Portability : portable (depends on GHC)
--
-- Manipulating stock icons
--
module Graphics.UI.Gtk.General.IconFactory (
-- * Detail
--
-- | Browse the available stock icons in the list of stock IDs found here. You
-- can also use the gtk-demo application for this purpose.
--
-- An icon factory manages a collection of 'IconSet'; a 'IconSet' manages a
-- set of variants of a particular icon (i.e. a 'IconSet' contains variants for
-- different sizes and widget states). Icons in an icon factory are named by a
-- stock ID, which is a simple string identifying the icon. Each 'Style' has a
-- list of 'IconFactory' derived from the current theme; those icon factories
-- are consulted first when searching for an icon. If the theme doesn't set a
-- particular icon, Gtk+ looks for the icon in a list of default icon
-- factories, maintained by 'iconFactoryAddDefault' and
-- 'iconFactoryRemoveDefault'. Applications with icons should add a default
-- icon factory with their icons, which will allow themes to override the icons
-- for the application.
--
-- To display an icon, always use
-- 'Graphics.UI.Gtk.General.Style.styleLookupIconSet' on the widget that
-- will display the icon, or the convenience function
-- 'Graphics.UI.Gtk.Abstract.Widget.widgetRenderIcon'. These
-- functions take the theme into account when looking up the icon to use for a
-- given stock ID.

-- * Class Hierarchy
-- |
-- @
-- | 'GObject'
-- | +----IconFactory
-- @

-- * Types
  IconFactory,
  IconFactoryClass,
  castToIconFactory, gTypeIconFactory,
  toIconFactory,

-- * Constructors
  iconFactoryNew,

-- * Methods
  iconFactoryAdd,
  iconFactoryAddDefault,
  iconFactoryLookup,
  iconFactoryLookupDefault,
  iconFactoryRemoveDefault,
  IconSet,
  iconSetNew,
  iconSetNewFromPixbuf,
  iconSetAddSource,
  iconSetRenderIcon,
  iconSetGetSizes,
  IconSource,
  iconSourceNew,
  TextDirection(..),
  iconSourceGetDirection,
  iconSourceSetDirection,
  iconSourceResetDirection,
  iconSourceGetFilename,
  iconSourceSetFilename,
  iconSourceGetPixbuf,
  iconSourceSetPixbuf,
  iconSourceGetSize,
  iconSourceSetSize,
  iconSourceResetSize,
  StateType(..),
  iconSourceGetState,
  iconSourceSetState,
  iconSourceResetState,
  IconSize(..),
  iconSizeCheck,
  iconSizeRegister,
  iconSizeRegisterAlias,
  iconSizeFromName,
  iconSizeGetName
  ) where

import Control.Applicative
import Prelude
import Control.Monad (liftM)

import System.Glib.FFI
import System.Glib.UTFString
import Graphics.UI.Gtk.Types
{-# LINE 113 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}
import Graphics.UI.Gtk.General.Enums (TextDirection(..), StateType(..))
import Graphics.UI.Gtk.General.StockItems
import Graphics.UI.Gtk.General.Structs (IconSize(..))


{-# LINE 118 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}

newtype IconSource = IconSource (ForeignPtr (IconSource))
{-# LINE 120 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}

newtype IconSet = IconSet (ForeignPtr (IconSet))
{-# LINE 122 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}

-- The Show instance for IconSize is here since we need c2hs.
instance Show IconSize where
  show :: IconSize -> String
show IconSize
i = IO String -> String
forall a. IO a -> a
unsafePerformIO (Int -> IO String
forall {a}. Integral a => a -> IO String
lookupSizeString (IconSize -> Int
forall a. Enum a => a -> Int
fromEnum IconSize
i))
    where
    lookupSizeString :: a -> IO String
lookupSizeString a
n = do
      Ptr CChar
ptr <- CInt -> IO (Ptr CChar)
gtk_icon_size_get_name (a -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n)
      if Ptr CChar
ptrPtr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
==Ptr CChar
forall a. Ptr a
nullPtr then String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"" else StockId -> String
glibToString (StockId -> String) -> IO StockId -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CChar -> IO StockId
forall s. GlibString s => Ptr CChar -> IO s
peekUTFString Ptr CChar
ptr

--------------------
-- Constructors

-- | Create a new IconFactory.
--
-- * An application should create a new 'IconFactory' and add all
-- needed icons.
-- By calling 'iconFactoryAddDefault' these icons become
-- available as stock objects and can easily be displayed by
-- 'Image'. Furthermore, a theme can override the icons defined by
-- the application.
--
iconFactoryNew :: IO IconFactory
iconFactoryNew :: IO IconFactory
iconFactoryNew =
  (ForeignPtr IconFactory -> IconFactory, FinalizerPtr IconFactory)
-> IO (Ptr IconFactory) -> IO IconFactory
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr IconFactory -> IconFactory, FinalizerPtr IconFactory)
forall {a}. (ForeignPtr IconFactory -> IconFactory, FinalizerPtr a)
mkIconFactory IO (Ptr IconFactory)
gtk_icon_factory_new
{-# LINE 146 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}

--------------------
-- Methods

-- | Add an IconSet to an IconFactory.
--
-- In order to use the new stock object, the factory as to be added to the
-- default factories by 'iconFactoryAddDefault'.
--
iconFactoryAdd :: IconFactory -> StockId -> IconSet -> IO ()
iconFactoryAdd :: IconFactory -> StockId -> IconSet -> IO ()
iconFactoryAdd IconFactory
i StockId
stockId IconSet
iconSet = StockId -> (Ptr CChar -> IO ()) -> IO ()
forall s a. GlibString s => s -> (Ptr CChar -> IO a) -> IO a
forall a. StockId -> (Ptr CChar -> IO a) -> IO a
withUTFString StockId
stockId ((Ptr CChar -> IO ()) -> IO ()) -> (Ptr CChar -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
strPtr ->
  (\(IconFactory ForeignPtr IconFactory
arg1) Ptr CChar
arg2 (IconSet ForeignPtr IconSet
arg3) -> ForeignPtr IconFactory -> (Ptr IconFactory -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconFactory
arg1 ((Ptr IconFactory -> IO ()) -> IO ())
-> (Ptr IconFactory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconFactory
argPtr1 ->ForeignPtr IconSet -> (Ptr IconSet -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSet
arg3 ((Ptr IconSet -> IO ()) -> IO ())
-> (Ptr IconSet -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSet
argPtr3 ->Ptr IconFactory -> Ptr CChar -> Ptr IconSet -> IO ()
gtk_icon_factory_add Ptr IconFactory
argPtr1 Ptr CChar
arg2 Ptr IconSet
argPtr3) IconFactory
i Ptr CChar
strPtr IconSet
iconSet

-- | Add all entries of the IconFactory to the
-- applications stock object database.
--
iconFactoryAddDefault :: IconFactory -> IO ()
iconFactoryAddDefault :: IconFactory -> IO ()
iconFactoryAddDefault = (\(IconFactory ForeignPtr IconFactory
arg1) -> ForeignPtr IconFactory -> (Ptr IconFactory -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconFactory
arg1 ((Ptr IconFactory -> IO ()) -> IO ())
-> (Ptr IconFactory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconFactory
argPtr1 ->Ptr IconFactory -> IO ()
gtk_icon_factory_add_default Ptr IconFactory
argPtr1)
{-# LINE 164 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}

-- | Looks up the stock id in the icon factory, returning an icon set if found,
-- otherwise Nothing.
--
-- For display to the user, you should use
-- 'Graphics.UI.Gtk.General.Style.styleLookupIconSet' on the
-- 'Graphics.UI.Gtk.General.Style.Style'
-- for the widget that will display the icon, instead of using this function
-- directly, so that themes are taken into account.
--
iconFactoryLookup :: IconFactory -> StockId -> IO (Maybe IconSet)
iconFactoryLookup :: IconFactory -> StockId -> IO (Maybe IconSet)
iconFactoryLookup IconFactory
i StockId
stockId =
  StockId -> (Ptr CChar -> IO (Maybe IconSet)) -> IO (Maybe IconSet)
forall s a. GlibString s => s -> (Ptr CChar -> IO a) -> IO a
forall a. StockId -> (Ptr CChar -> IO a) -> IO a
withUTFString StockId
stockId ((Ptr CChar -> IO (Maybe IconSet)) -> IO (Maybe IconSet))
-> (Ptr CChar -> IO (Maybe IconSet)) -> IO (Maybe IconSet)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
strPtr -> do
  Ptr IconSet
iconSetPtr <- (\(IconFactory ForeignPtr IconFactory
arg1) Ptr CChar
arg2 -> ForeignPtr IconFactory
-> (Ptr IconFactory -> IO (Ptr IconSet)) -> IO (Ptr IconSet)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconFactory
arg1 ((Ptr IconFactory -> IO (Ptr IconSet)) -> IO (Ptr IconSet))
-> (Ptr IconFactory -> IO (Ptr IconSet)) -> IO (Ptr IconSet)
forall a b. (a -> b) -> a -> b
$ \Ptr IconFactory
argPtr1 ->Ptr IconFactory -> Ptr CChar -> IO (Ptr IconSet)
gtk_icon_factory_lookup Ptr IconFactory
argPtr1 Ptr CChar
arg2) IconFactory
i Ptr CChar
strPtr
  if Ptr IconSet
iconSetPtr Ptr IconSet -> Ptr IconSet -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr IconSet
forall a. Ptr a
nullPtr then Maybe IconSet -> IO (Maybe IconSet)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconSet
forall a. Maybe a
Nothing else (ForeignPtr IconSet -> Maybe IconSet)
-> IO (ForeignPtr IconSet) -> IO (Maybe IconSet)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (IconSet -> Maybe IconSet
forall a. a -> Maybe a
Just (IconSet -> Maybe IconSet)
-> (ForeignPtr IconSet -> IconSet)
-> ForeignPtr IconSet
-> Maybe IconSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr IconSet -> IconSet
IconSet) (IO (ForeignPtr IconSet) -> IO (Maybe IconSet))
-> IO (ForeignPtr IconSet) -> IO (Maybe IconSet)
forall a b. (a -> b) -> a -> b
$
    Ptr IconSet -> FinalizerPtr IconSet -> IO (ForeignPtr IconSet)
forall a. Ptr a -> FinalizerPtr a -> IO (ForeignPtr a)
newForeignPtr Ptr IconSet
iconSetPtr FinalizerPtr IconSet
icon_set_unref

-- | Looks for an icon in the list of default icon factories.
--
-- For display to the user, you should use
-- 'Graphics.UI.Gtk.General.Style.styleLookupIconSet' on the
-- 'Graphics.UI.Gtk.General.Style.Style'
-- for the widget that will display the icon, instead of using this function
-- directly, so that themes are taken into account.
--
iconFactoryLookupDefault :: StockId -> IO (Maybe IconSet)
iconFactoryLookupDefault :: StockId -> IO (Maybe IconSet)
iconFactoryLookupDefault StockId
stockId =
  StockId -> (Ptr CChar -> IO (Maybe IconSet)) -> IO (Maybe IconSet)
forall s a. GlibString s => s -> (Ptr CChar -> IO a) -> IO a
forall a. StockId -> (Ptr CChar -> IO a) -> IO a
withUTFString StockId
stockId ((Ptr CChar -> IO (Maybe IconSet)) -> IO (Maybe IconSet))
-> (Ptr CChar -> IO (Maybe IconSet)) -> IO (Maybe IconSet)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
strPtr -> do
  Ptr IconSet
iconSetPtr <- Ptr CChar -> IO (Ptr IconSet)
gtk_icon_factory_lookup_default Ptr CChar
strPtr
  if Ptr IconSet
iconSetPtr Ptr IconSet -> Ptr IconSet -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr IconSet
forall a. Ptr a
nullPtr then Maybe IconSet -> IO (Maybe IconSet)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconSet
forall a. Maybe a
Nothing else (ForeignPtr IconSet -> Maybe IconSet)
-> IO (ForeignPtr IconSet) -> IO (Maybe IconSet)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (IconSet -> Maybe IconSet
forall a. a -> Maybe a
Just (IconSet -> Maybe IconSet)
-> (ForeignPtr IconSet -> IconSet)
-> ForeignPtr IconSet
-> Maybe IconSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr IconSet -> IconSet
IconSet) (IO (ForeignPtr IconSet) -> IO (Maybe IconSet))
-> IO (ForeignPtr IconSet) -> IO (Maybe IconSet)
forall a b. (a -> b) -> a -> b
$
    Ptr IconSet -> FinalizerPtr IconSet -> IO (ForeignPtr IconSet)
forall a. Ptr a -> FinalizerPtr a -> IO (ForeignPtr a)
newForeignPtr Ptr IconSet
iconSetPtr FinalizerPtr IconSet
icon_set_unref

-- | Remove an IconFactory from the
-- application's stock database.
--
iconFactoryRemoveDefault :: IconFactory -> IO ()
iconFactoryRemoveDefault :: IconFactory -> IO ()
iconFactoryRemoveDefault = (\(IconFactory ForeignPtr IconFactory
arg1) -> ForeignPtr IconFactory -> (Ptr IconFactory -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconFactory
arg1 ((Ptr IconFactory -> IO ()) -> IO ())
-> (Ptr IconFactory -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconFactory
argPtr1 ->Ptr IconFactory -> IO ()
gtk_icon_factory_remove_default Ptr IconFactory
argPtr1)
{-# LINE 201 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}

-- | Add an 'IconSource' (an Icon with
-- attributes) to an 'IconSet'.
--
-- * If an icon is looked up in the IconSet @set@ the best matching
-- IconSource will be taken. It is therefore advisable to add a default
-- (wildcarded) icon, than can be used if no exact match is found.
--
iconSetAddSource :: IconSet -> IconSource -> IO ()
iconSetAddSource :: IconSet -> IconSource -> IO ()
iconSetAddSource IconSet
set IconSource
source = (\(IconSet ForeignPtr IconSet
arg1) (IconSource ForeignPtr IconSource
arg2) -> ForeignPtr IconSet -> (Ptr IconSet -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSet
arg1 ((Ptr IconSet -> IO ()) -> IO ())
-> (Ptr IconSet -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSet
argPtr1 ->ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg2 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr2 ->Ptr IconSet -> Ptr IconSource -> IO ()
gtk_icon_set_add_source Ptr IconSet
argPtr1 Ptr IconSource
argPtr2) IconSet
set IconSource
source

iconSetRenderIcon :: WidgetClass widget => IconSet
                  -> TextDirection
                  -> StateType
                  -> IconSize
                  -> widget
                  -> IO Pixbuf
iconSetRenderIcon :: forall widget.
WidgetClass widget =>
IconSet
-> TextDirection -> StateType -> IconSize -> widget -> IO Pixbuf
iconSetRenderIcon IconSet
set TextDirection
dir StateType
state IconSize
size widget
widget = (ForeignPtr Pixbuf -> Pixbuf, FinalizerPtr Pixbuf)
-> IO (Ptr Pixbuf) -> IO Pixbuf
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
wrapNewGObject (ForeignPtr Pixbuf -> Pixbuf, FinalizerPtr Pixbuf)
forall {a}. (ForeignPtr Pixbuf -> Pixbuf, FinalizerPtr a)
mkPixbuf (IO (Ptr Pixbuf) -> IO Pixbuf) -> IO (Ptr Pixbuf) -> IO Pixbuf
forall a b. (a -> b) -> a -> b
$
  (\(IconSet ForeignPtr IconSet
arg1) (Style ForeignPtr Style
arg2) CInt
arg3 CInt
arg4 CInt
arg5 (Widget ForeignPtr Widget
arg6) Ptr CChar
arg7 -> ForeignPtr IconSet
-> (Ptr IconSet -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSet
arg1 ((Ptr IconSet -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr IconSet -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr IconSet
argPtr1 ->ForeignPtr Style
-> (Ptr Style -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Style
arg2 ((Ptr Style -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr Style -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Style
argPtr2 ->ForeignPtr Widget
-> (Ptr Widget -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Widget
arg6 ((Ptr Widget -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr Widget -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
argPtr6 ->Ptr IconSet
-> Ptr Style
-> CInt
-> CInt
-> CInt
-> Ptr Widget
-> Ptr CChar
-> IO (Ptr Pixbuf)
gtk_icon_set_render_icon Ptr IconSet
argPtr1 Ptr Style
argPtr2 CInt
arg3 CInt
arg4 CInt
arg5 Ptr Widget
argPtr6 Ptr CChar
arg7) IconSet
set (ForeignPtr Style -> Style
Style ForeignPtr Style
forall a. ForeignPtr a
nullForeignPtr)
    ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Int -> CInt) -> (TextDirection -> Int) -> TextDirection -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
.TextDirection -> Int
forall a. Enum a => a -> Int
fromEnum) TextDirection
dir) ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Int -> CInt) -> (StateType -> Int) -> StateType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
.StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
state)
    ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Int -> CInt) -> (IconSize -> Int) -> IconSize -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
.IconSize -> Int
forall a. Enum a => a -> Int
fromEnum) IconSize
size) (widget -> Widget
forall o. WidgetClass o => o -> Widget
toWidget widget
widget) Ptr CChar
forall a. Ptr a
nullPtr

-- | Create a new IconSet.
--
-- * Each icon in an application is contained in an 'IconSet'. The
-- 'IconSet' contains several variants ('IconSource's) to
-- accomodate for different sizes and states.
--
iconSetNew :: IO IconSet
iconSetNew :: IO IconSet
iconSetNew = do
  Ptr IconSet
isPtr <- IO (Ptr IconSet)
gtk_icon_set_new
{-# LINE 232 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}
  liftM IconSet $ newForeignPtr isPtr icon_set_unref

-- | Creates a new 'IconSet' with the given pixbuf as the default\/fallback
-- source image. If you don't add any additional "IconSource" to the icon set,
-- all variants of the icon will be created from the pixbuf, using scaling,
-- pixelation, etc. as required to adjust the icon size or make the icon look
-- insensitive\/prelighted.
--
iconSetNewFromPixbuf :: Pixbuf -> IO IconSet
iconSetNewFromPixbuf :: Pixbuf -> IO IconSet
iconSetNewFromPixbuf Pixbuf
pixbuf = do
  Ptr IconSet
isPtr <- (\(Pixbuf ForeignPtr Pixbuf
arg1) -> ForeignPtr Pixbuf
-> (Ptr Pixbuf -> IO (Ptr IconSet)) -> IO (Ptr IconSet)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Pixbuf
arg1 ((Ptr Pixbuf -> IO (Ptr IconSet)) -> IO (Ptr IconSet))
-> (Ptr Pixbuf -> IO (Ptr IconSet)) -> IO (Ptr IconSet)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
argPtr1 ->Ptr Pixbuf -> IO (Ptr IconSet)
gtk_icon_set_new_from_pixbuf Ptr Pixbuf
argPtr1) Pixbuf
pixbuf
  (ForeignPtr IconSet -> IconSet)
-> IO (ForeignPtr IconSet) -> IO IconSet
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ForeignPtr IconSet -> IconSet
IconSet (IO (ForeignPtr IconSet) -> IO IconSet)
-> IO (ForeignPtr IconSet) -> IO IconSet
forall a b. (a -> b) -> a -> b
$ Ptr IconSet -> FinalizerPtr IconSet -> IO (ForeignPtr IconSet)
forall a. Ptr a -> FinalizerPtr a -> IO (ForeignPtr a)
newForeignPtr Ptr IconSet
isPtr FinalizerPtr IconSet
icon_set_unref

-- | Obtains a list of icon sizes this icon set can render.
--
iconSetGetSizes :: IconSet -> IO [IconSize]
iconSetGetSizes :: IconSet -> IO [IconSize]
iconSetGetSizes IconSet
set =
  (Ptr (Ptr CInt) -> IO [IconSize]) -> IO [IconSize]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr CInt) -> IO [IconSize]) -> IO [IconSize])
-> (Ptr (Ptr CInt) -> IO [IconSize]) -> IO [IconSize]
forall a b. (a -> b) -> a -> b
$ \Ptr (Ptr CInt)
sizesArrPtr -> (Ptr CInt -> IO [IconSize]) -> IO [IconSize]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO [IconSize]) -> IO [IconSize])
-> (Ptr CInt -> IO [IconSize]) -> IO [IconSize]
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
lenPtr -> do
  (\(IconSet ForeignPtr IconSet
arg1) Ptr (Ptr CInt)
arg2 Ptr CInt
arg3 -> ForeignPtr IconSet -> (Ptr IconSet -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSet
arg1 ((Ptr IconSet -> IO ()) -> IO ())
-> (Ptr IconSet -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSet
argPtr1 ->Ptr IconSet -> Ptr (Ptr CInt) -> Ptr CInt -> IO ()
gtk_icon_set_get_sizes Ptr IconSet
argPtr1 Ptr (Ptr CInt)
arg2 Ptr CInt
arg3) IconSet
set Ptr (Ptr CInt)
sizesArrPtr Ptr CInt
lenPtr
  CInt
len <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
lenPtr
  Ptr CInt
sizesArr <- Ptr (Ptr CInt) -> IO (Ptr CInt)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CInt)
sizesArrPtr
  [CInt]
list <- Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
len) Ptr CInt
sizesArr
  Ptr () -> IO ()
g_free (Ptr CInt -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CInt
sizesArr)
  [IconSize] -> IO [IconSize]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([IconSize] -> IO [IconSize]) -> [IconSize] -> IO [IconSize]
forall a b. (a -> b) -> a -> b
$ (CInt -> IconSize) -> [CInt] -> [IconSize]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> IconSize
forall a. Enum a => Int -> a
toEnum(Int -> IconSize) -> (CInt -> Int) -> CInt -> IconSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
.CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) [CInt]
list

foreign import ccall unsafe "&gtk_icon_set_unref"
  icon_set_unref :: FinalizerPtr IconSet

-- | Check if a given IconSize is registered.
--
-- * Useful if your application expects a theme to install a set with a
-- specific size. You can test if this actually happend and use another size
-- if not.
--
iconSizeCheck :: IconSize -> IO Bool
iconSizeCheck :: IconSize -> IO Bool
iconSizeCheck IconSize
size = (CInt -> Bool) -> IO CInt -> IO Bool
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CInt -> IO Bool) -> IO CInt -> IO Bool
forall a b. (a -> b) -> a -> b
$
  CInt -> Ptr CInt -> Ptr CInt -> IO CInt
gtk_icon_size_lookup ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (IconSize -> Int) -> IconSize -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IconSize -> Int
forall a. Enum a => a -> Int
fromEnum) IconSize
size) Ptr CInt
forall a. Ptr a
nullPtr Ptr CInt
forall a. Ptr a
nullPtr

-- | Register a new IconSize.
--
iconSizeRegister :: GlibString string
  => string -- ^ the new name of the size
  -> Int -- ^ the width of the icon
  -> Int -- ^ the height of the icon
  -> IO IconSize -- ^ the new icon size
iconSizeRegister :: forall string.
GlibString string =>
string -> Int -> Int -> IO IconSize
iconSizeRegister string
name Int
width Int
height = (CInt -> IconSize) -> IO CInt -> IO IconSize
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int -> IconSize
forall a. Enum a => Int -> a
toEnum (Int -> IconSize) -> (CInt -> Int) -> CInt -> IconSize
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 IconSize) -> IO CInt -> IO IconSize
forall a b. (a -> b) -> a -> b
$
  string -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. string -> (Ptr CChar -> IO a) -> IO a
forall s a. GlibString s => s -> (Ptr CChar -> IO a) -> IO a
withUTFString string
name ((Ptr CChar -> IO CInt) -> IO CInt)
-> (Ptr CChar -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
strPtr -> Ptr CChar -> CInt -> CInt -> IO CInt
gtk_icon_size_register
{-# LINE 279 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}
  strPtr (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
height)

-- | Register an additional alias for a name.
--
iconSizeRegisterAlias :: GlibString string => IconSize -> string -> IO ()
iconSizeRegisterAlias :: forall string. GlibString string => IconSize -> string -> IO ()
iconSizeRegisterAlias IconSize
target string
alias = string -> (Ptr CChar -> IO ()) -> IO ()
forall a. string -> (Ptr CChar -> IO a) -> IO a
forall s a. GlibString s => s -> (Ptr CChar -> IO a) -> IO a
withUTFString string
alias ((Ptr CChar -> IO ()) -> IO ()) -> (Ptr CChar -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
strPtr ->
  Ptr CChar -> CInt -> IO ()
gtk_icon_size_register_alias Ptr CChar
strPtr ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (IconSize -> Int) -> IconSize -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IconSize -> Int
forall a. Enum a => a -> Int
fromEnum) IconSize
target)

-- | Lookup an IconSize by name.
--
-- * This fixed value 'iconSizeInvalid' is returned if the name was
-- not found.
--
iconSizeFromName :: GlibString string => string -> IO IconSize
iconSizeFromName :: forall string. GlibString string => string -> IO IconSize
iconSizeFromName string
name = (CInt -> IconSize) -> IO CInt -> IO IconSize
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int -> IconSize
forall a. Enum a => Int -> a
toEnum (Int -> IconSize) -> (CInt -> Int) -> CInt -> IconSize
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 IconSize) -> IO CInt -> IO IconSize
forall a b. (a -> b) -> a -> b
$
  string -> (Ptr CChar -> IO CInt) -> IO CInt
forall a. string -> (Ptr CChar -> IO a) -> IO a
forall s a. GlibString s => s -> (Ptr CChar -> IO a) -> IO a
withUTFString string
name Ptr CChar -> IO CInt
gtk_icon_size_from_name
{-# LINE 295 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}

-- | Lookup the name of an IconSize.
--
-- * Returns @Nothing@ if the name was not found.
--
iconSizeGetName :: GlibString string => IconSize -> IO (Maybe string)
iconSizeGetName :: forall string. GlibString string => IconSize -> IO (Maybe string)
iconSizeGetName IconSize
size = do
  Ptr CChar
strPtr <- CInt -> IO (Ptr CChar)
gtk_icon_size_get_name ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (IconSize -> Int) -> IconSize -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IconSize -> Int
forall a. Enum a => a -> Int
fromEnum) IconSize
size)
  if Ptr CChar
strPtrPtr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
==Ptr CChar
forall a. Ptr a
nullPtr then Maybe string -> IO (Maybe string)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe string
forall a. Maybe a
Nothing else (string -> Maybe string) -> IO string -> IO (Maybe string)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM string -> Maybe string
forall a. a -> Maybe a
Just (IO string -> IO (Maybe string)) -> IO string -> IO (Maybe string)
forall a b. (a -> b) -> a -> b
$ Ptr CChar -> IO string
forall s. GlibString s => Ptr CChar -> IO s
peekUTFString Ptr CChar
strPtr

-- | Retrieve the 'TextDirection' of
-- this IconSource.
--
-- * @Nothing@ is returned if no explicit direction was set.
--
iconSourceGetDirection :: IconSource -> IO (Maybe TextDirection)
iconSourceGetDirection :: IconSource -> IO (Maybe TextDirection)
iconSourceGetDirection IconSource
is = do
  CInt
res <- (\(IconSource ForeignPtr IconSource
arg1) -> ForeignPtr IconSource -> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO CInt) -> IO CInt)
-> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> IO CInt
gtk_icon_source_get_direction_wildcarded Ptr IconSource
argPtr1) IconSource
is
  if (CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CInt
res) then Maybe TextDirection -> IO (Maybe TextDirection)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TextDirection
forall a. Maybe a
Nothing else (CInt -> Maybe TextDirection)
-> IO CInt -> IO (Maybe TextDirection)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (TextDirection -> Maybe TextDirection
forall a. a -> Maybe a
Just (TextDirection -> Maybe TextDirection)
-> (CInt -> TextDirection) -> CInt -> Maybe TextDirection
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Int -> TextDirection
forall a. Enum a => Int -> a
toEnum(Int -> TextDirection) -> (CInt -> Int) -> CInt -> TextDirection
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 (Maybe TextDirection))
-> IO CInt -> IO (Maybe TextDirection)
forall a b. (a -> b) -> a -> b
$
    (\(IconSource ForeignPtr IconSource
arg1) -> ForeignPtr IconSource -> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO CInt) -> IO CInt)
-> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> IO CInt
gtk_icon_source_get_direction Ptr IconSource
argPtr1) IconSource
is

-- | Retrieve the filename this IconSource was
-- based on.
--
-- * Returns @Nothing@ if the IconSource was generated by a Pixbuf.
--
iconSourceGetFilename :: GlibString string => IconSource -> IO (Maybe string)
iconSourceGetFilename :: forall string. GlibString string => IconSource -> IO (Maybe string)
iconSourceGetFilename IconSource
is = do



  Ptr CChar
strPtr <- (\(IconSource ForeignPtr IconSource
arg1) -> ForeignPtr IconSource
-> (Ptr IconSource -> IO (Ptr CChar)) -> IO (Ptr CChar)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO (Ptr CChar)) -> IO (Ptr CChar))
-> (Ptr IconSource -> IO (Ptr CChar)) -> IO (Ptr CChar)
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> IO (Ptr CChar)
gtk_icon_source_get_filename Ptr IconSource
argPtr1) IconSource
is

  if Ptr CChar
strPtrPtr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
==Ptr CChar
forall a. Ptr a
nullPtr then Maybe string -> IO (Maybe string)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe string
forall a. Maybe a
Nothing else (string -> Maybe string) -> IO string -> IO (Maybe string)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM string -> Maybe string
forall a. a -> Maybe a
Just (IO string -> IO (Maybe string)) -> IO string -> IO (Maybe string)
forall a b. (a -> b) -> a -> b
$ Ptr CChar -> IO string
forall s. GlibString s => Ptr CChar -> IO s
peekUTFString Ptr CChar
strPtr

-- | Retrieve the 'IconSize' of this
-- IconSource.
--
-- * @Nothing@ is returned if no explicit size was set (i.e. this
-- 'IconSource' matches all sizes).
--
iconSourceGetSize :: IconSource -> IO (Maybe IconSize)
iconSourceGetSize :: IconSource -> IO (Maybe IconSize)
iconSourceGetSize IconSource
is = do
  CInt
res <- (\(IconSource ForeignPtr IconSource
arg1) -> ForeignPtr IconSource -> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO CInt) -> IO CInt)
-> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> IO CInt
gtk_icon_source_get_size_wildcarded Ptr IconSource
argPtr1) IconSource
is
  if (CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CInt
res) then Maybe IconSize -> IO (Maybe IconSize)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconSize
forall a. Maybe a
Nothing else (CInt -> Maybe IconSize) -> IO CInt -> IO (Maybe IconSize)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (IconSize -> Maybe IconSize
forall a. a -> Maybe a
Just (IconSize -> Maybe IconSize)
-> (CInt -> IconSize) -> CInt -> Maybe IconSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IconSize
forall a. Enum a => Int -> a
toEnum (Int -> IconSize) -> (CInt -> Int) -> CInt -> IconSize
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 (Maybe IconSize)) -> IO CInt -> IO (Maybe IconSize)
forall a b. (a -> b) -> a -> b
$
    (\(IconSource ForeignPtr IconSource
arg1) -> ForeignPtr IconSource -> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO CInt) -> IO CInt)
-> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> IO CInt
gtk_icon_source_get_size Ptr IconSource
argPtr1) IconSource
is

-- | Retrieve the 'StateType' of this
-- 'IconSource'.
--
-- * @Nothing@ is returned if the 'IconSource' matches all
-- states.
--
iconSourceGetState :: IconSource -> IO (Maybe StateType)
iconSourceGetState :: IconSource -> IO (Maybe StateType)
iconSourceGetState IconSource
is = do
  CInt
res <- (\(IconSource ForeignPtr IconSource
arg1) -> ForeignPtr IconSource -> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO CInt) -> IO CInt)
-> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> IO CInt
gtk_icon_source_get_state_wildcarded Ptr IconSource
argPtr1) IconSource
is
  if (CInt -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CInt
res) then Maybe StateType -> IO (Maybe StateType)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StateType
forall a. Maybe a
Nothing else (CInt -> Maybe StateType) -> IO CInt -> IO (Maybe StateType)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (StateType -> Maybe StateType
forall a. a -> Maybe a
Just (StateType -> Maybe StateType)
-> (CInt -> StateType) -> CInt -> Maybe StateType
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Int -> StateType
forall a. Enum a => Int -> a
toEnum(Int -> StateType) -> (CInt -> Int) -> CInt -> StateType
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 (Maybe StateType))
-> IO CInt -> IO (Maybe StateType)
forall a b. (a -> b) -> a -> b
$
    (\(IconSource ForeignPtr IconSource
arg1) -> ForeignPtr IconSource -> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO CInt) -> IO CInt)
-> (Ptr IconSource -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> IO CInt
gtk_icon_source_get_state Ptr IconSource
argPtr1) IconSource
is

-- | Create a new IconSource.
--
-- * An IconSource is a single image that is usually added to an IconSet. Next
-- to the image it contains information about which state, text direction
-- and size it should apply.
--
iconSourceNew :: IO IconSource
iconSourceNew :: IO IconSource
iconSourceNew = do
  Ptr IconSource
isPtr <- IO (Ptr IconSource)
gtk_icon_source_new
{-# LINE 363 "./Graphics/UI/Gtk/General/IconFactory.chs" #-}
  liftM IconSource $ newForeignPtr isPtr icon_source_free

foreign import ccall unsafe "&gtk_icon_source_free"
  icon_source_free :: FinalizerPtr IconSource

-- | Mark this 'IconSource' that it
-- should only apply to the specified 'TextDirection'.
--
iconSourceSetDirection :: IconSource -> TextDirection -> IO ()
iconSourceSetDirection :: IconSource -> TextDirection -> IO ()
iconSourceSetDirection IconSource
is TextDirection
td = do
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_direction_wildcarded Ptr IconSource
argPtr1 CInt
arg2) IconSource
is (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
False)
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_direction Ptr IconSource
argPtr1 CInt
arg2) IconSource
is ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Int -> CInt) -> (TextDirection -> Int) -> TextDirection -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
.TextDirection -> Int
forall a. Enum a => a -> Int
fromEnum) TextDirection
td)

-- | Reset the specific
-- 'TextDirection' set with 'iconSourceSetDirection'.
--
iconSourceResetDirection :: IconSource -> IO ()
iconSourceResetDirection :: IconSource -> IO ()
iconSourceResetDirection IconSource
is =
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_direction_wildcarded Ptr IconSource
argPtr1 CInt
arg2) IconSource
is (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
True)

-- | Load an icon picture from this filename.
--
iconSourceSetFilename :: GlibFilePath fp => IconSource -> fp -> IO ()
iconSourceSetFilename :: forall fp. GlibFilePath fp => IconSource -> fp -> IO ()
iconSourceSetFilename IconSource
is fp
name =



  fp -> (Ptr CChar -> IO ()) -> IO ()
forall a. fp -> (Ptr CChar -> IO a) -> IO a
forall fp a. GlibFilePath fp => fp -> (Ptr CChar -> IO a) -> IO a
withUTFFilePath fp
name ((Ptr CChar -> IO ()) -> IO ()) -> (Ptr CChar -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ (\(IconSource ForeignPtr IconSource
arg1) Ptr CChar
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> Ptr CChar -> IO ()
gtk_icon_source_set_filename Ptr IconSource
argPtr1 Ptr CChar
arg2) IconSource
is


-- | Retrieves the source pixbuf, or Nothing if none is set.
--
iconSourceGetPixbuf :: IconSource -> IO (Maybe Pixbuf)
iconSourceGetPixbuf :: IconSource -> IO (Maybe Pixbuf)
iconSourceGetPixbuf IconSource
is = (IO (Ptr Pixbuf) -> IO Pixbuf)
-> IO (Ptr Pixbuf) -> IO (Maybe Pixbuf)
forall a. (IO (Ptr a) -> IO a) -> IO (Ptr a) -> IO (Maybe a)
maybeNull ((ForeignPtr Pixbuf -> Pixbuf, FinalizerPtr Pixbuf)
-> IO (Ptr Pixbuf) -> IO Pixbuf
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewGObject (ForeignPtr Pixbuf -> Pixbuf, FinalizerPtr Pixbuf)
forall {a}. (ForeignPtr Pixbuf -> Pixbuf, FinalizerPtr a)
mkPixbuf) (IO (Ptr Pixbuf) -> IO (Maybe Pixbuf))
-> IO (Ptr Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$
  (\(IconSource ForeignPtr IconSource
arg1) -> ForeignPtr IconSource
-> (Ptr IconSource -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf))
-> (Ptr IconSource -> IO (Ptr Pixbuf)) -> IO (Ptr Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> IO (Ptr Pixbuf)
gtk_icon_source_get_pixbuf Ptr IconSource
argPtr1) IconSource
is

-- | Sets a pixbuf to use as a base image when creating icon variants for
-- 'IconSet'.
--
iconSourceSetPixbuf :: IconSource -> Pixbuf -> IO ()
iconSourceSetPixbuf :: IconSource -> Pixbuf -> IO ()
iconSourceSetPixbuf IconSource
is Pixbuf
pb = do
  (\(IconSource ForeignPtr IconSource
arg1) (Pixbuf ForeignPtr Pixbuf
arg2) -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->ForeignPtr Pixbuf -> (Ptr Pixbuf -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Pixbuf
arg2 ((Ptr Pixbuf -> IO ()) -> IO ()) -> (Ptr Pixbuf -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
argPtr2 ->Ptr IconSource -> Ptr Pixbuf -> IO ()
gtk_icon_source_set_pixbuf Ptr IconSource
argPtr1 Ptr Pixbuf
argPtr2) IconSource
is Pixbuf
pb

-- | Set this 'IconSource' to a specific
-- size.
--
iconSourceSetSize :: IconSource -> IconSize -> IO ()
iconSourceSetSize :: IconSource -> IconSize -> IO ()
iconSourceSetSize IconSource
is IconSize
size = do
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_size_wildcarded Ptr IconSource
argPtr1 CInt
arg2) IconSource
is (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
False)
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_size Ptr IconSource
argPtr1 CInt
arg2) IconSource
is ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (IconSize -> Int) -> IconSize -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IconSize -> Int
forall a. Enum a => a -> Int
fromEnum) IconSize
size)

-- | Reset the 'IconSize' of this
-- 'IconSource' so that is matches anything.
--
iconSourceResetSize :: IconSource -> IO ()
iconSourceResetSize :: IconSource -> IO ()
iconSourceResetSize IconSource
is =
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_size_wildcarded Ptr IconSource
argPtr1 CInt
arg2) IconSource
is (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
True)

-- | Mark this icon to be used only with this
-- specific state.
--
iconSourceSetState :: IconSource -> StateType -> IO ()
iconSourceSetState :: IconSource -> StateType -> IO ()
iconSourceSetState IconSource
is StateType
state = do
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_state_wildcarded Ptr IconSource
argPtr1 CInt
arg2) IconSource
is (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
False)
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_state Ptr IconSource
argPtr1 CInt
arg2) IconSource
is ((Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Int -> CInt) -> (StateType -> Int) -> StateType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
.StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
state)

-- | Reset the 'StateType' of this
-- 'IconSource' so that is matches anything.
--
iconSourceResetState :: IconSource -> IO ()
iconSourceResetState :: IconSource -> IO ()
iconSourceResetState IconSource
is =
  (\(IconSource ForeignPtr IconSource
arg1) CInt
arg2 -> ForeignPtr IconSource -> (Ptr IconSource -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr IconSource
arg1 ((Ptr IconSource -> IO ()) -> IO ())
-> (Ptr IconSource -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr IconSource
argPtr1 ->Ptr IconSource -> CInt -> IO ()
gtk_icon_source_set_state_wildcarded Ptr IconSource
argPtr1 CInt
arg2) IconSource
is (Bool -> CInt
forall a. Num a => Bool -> a
fromBool Bool
True)

foreign import ccall unsafe "gtk_icon_size_get_name"
  gtk_icon_size_get_name :: (CInt -> (IO (Ptr CChar)))

foreign import ccall unsafe "gtk_icon_factory_new"
  gtk_icon_factory_new :: (IO (Ptr IconFactory))

foreign import ccall unsafe "gtk_icon_factory_add"
  gtk_icon_factory_add :: ((Ptr IconFactory) -> ((Ptr CChar) -> ((Ptr IconSet) -> (IO ()))))

foreign import ccall unsafe "gtk_icon_factory_add_default"
  gtk_icon_factory_add_default :: ((Ptr IconFactory) -> (IO ()))

foreign import ccall unsafe "gtk_icon_factory_lookup"
  gtk_icon_factory_lookup :: ((Ptr IconFactory) -> ((Ptr CChar) -> (IO (Ptr IconSet))))

foreign import ccall unsafe "gtk_icon_factory_lookup_default"
  gtk_icon_factory_lookup_default :: ((Ptr CChar) -> (IO (Ptr IconSet)))

foreign import ccall unsafe "gtk_icon_factory_remove_default"
  gtk_icon_factory_remove_default :: ((Ptr IconFactory) -> (IO ()))

foreign import ccall unsafe "gtk_icon_set_add_source"
  gtk_icon_set_add_source :: ((Ptr IconSet) -> ((Ptr IconSource) -> (IO ())))

foreign import ccall safe "gtk_icon_set_render_icon"
  gtk_icon_set_render_icon :: ((Ptr IconSet) -> ((Ptr Style) -> (CInt -> (CInt -> (CInt -> ((Ptr Widget) -> ((Ptr CChar) -> (IO (Ptr Pixbuf)))))))))

foreign import ccall unsafe "gtk_icon_set_new"
  gtk_icon_set_new :: (IO (Ptr IconSet))

foreign import ccall unsafe "gtk_icon_set_new_from_pixbuf"
  gtk_icon_set_new_from_pixbuf :: ((Ptr Pixbuf) -> (IO (Ptr IconSet)))

foreign import ccall unsafe "gtk_icon_set_get_sizes"
  gtk_icon_set_get_sizes :: ((Ptr IconSet) -> ((Ptr (Ptr CInt)) -> ((Ptr CInt) -> (IO ()))))

foreign import ccall unsafe "g_free"
  g_free :: ((Ptr ()) -> (IO ()))

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

foreign import ccall unsafe "gtk_icon_size_register"
  gtk_icon_size_register :: ((Ptr CChar) -> (CInt -> (CInt -> (IO CInt))))

foreign import ccall unsafe "gtk_icon_size_register_alias"
  gtk_icon_size_register_alias :: ((Ptr CChar) -> (CInt -> (IO ())))

foreign import ccall unsafe "gtk_icon_size_from_name"
  gtk_icon_size_from_name :: ((Ptr CChar) -> (IO CInt))

foreign import ccall safe "gtk_icon_source_get_direction_wildcarded"
  gtk_icon_source_get_direction_wildcarded :: ((Ptr IconSource) -> (IO CInt))

foreign import ccall unsafe "gtk_icon_source_get_direction"
  gtk_icon_source_get_direction :: ((Ptr IconSource) -> (IO CInt))

foreign import ccall unsafe "gtk_icon_source_get_filename"
  gtk_icon_source_get_filename :: ((Ptr IconSource) -> (IO (Ptr CChar)))

foreign import ccall unsafe "gtk_icon_source_get_size_wildcarded"
  gtk_icon_source_get_size_wildcarded :: ((Ptr IconSource) -> (IO CInt))

foreign import ccall unsafe "gtk_icon_source_get_size"
  gtk_icon_source_get_size :: ((Ptr IconSource) -> (IO CInt))

foreign import ccall unsafe "gtk_icon_source_get_state_wildcarded"
  gtk_icon_source_get_state_wildcarded :: ((Ptr IconSource) -> (IO CInt))

foreign import ccall unsafe "gtk_icon_source_get_state"
  gtk_icon_source_get_state :: ((Ptr IconSource) -> (IO CInt))

foreign import ccall unsafe "gtk_icon_source_new"
  gtk_icon_source_new :: (IO (Ptr IconSource))

foreign import ccall unsafe "gtk_icon_source_set_direction_wildcarded"
  gtk_icon_source_set_direction_wildcarded :: ((Ptr IconSource) -> (CInt -> (IO ())))

foreign import ccall unsafe "gtk_icon_source_set_direction"
  gtk_icon_source_set_direction :: ((Ptr IconSource) -> (CInt -> (IO ())))

foreign import ccall unsafe "gtk_icon_source_set_filename"
  gtk_icon_source_set_filename :: ((Ptr IconSource) -> ((Ptr CChar) -> (IO ())))

foreign import ccall unsafe "gtk_icon_source_get_pixbuf"
  gtk_icon_source_get_pixbuf :: ((Ptr IconSource) -> (IO (Ptr Pixbuf)))

foreign import ccall safe "gtk_icon_source_set_pixbuf"
  gtk_icon_source_set_pixbuf :: ((Ptr IconSource) -> ((Ptr Pixbuf) -> (IO ())))

foreign import ccall unsafe "gtk_icon_source_set_size_wildcarded"
  gtk_icon_source_set_size_wildcarded :: ((Ptr IconSource) -> (CInt -> (IO ())))

foreign import ccall unsafe "gtk_icon_source_set_size"
  gtk_icon_source_set_size :: ((Ptr IconSource) -> (CInt -> (IO ())))

foreign import ccall unsafe "gtk_icon_source_set_state_wildcarded"
  gtk_icon_source_set_state_wildcarded :: ((Ptr IconSource) -> (CInt -> (IO ())))

foreign import ccall unsafe "gtk_icon_source_set_state"
  gtk_icon_source_set_state :: ((Ptr IconSource) -> (CInt -> (IO ())))