From: Andy S. <And...@co...> - 2010-03-28 14:50:40
|
Sun Mar 28 10:48:38 EDT 2010 Andy Stewart <laz...@gm...> * Add `IconTheme` module, Update `Recent` modules, and fix doc. Ignore-this: 95b29182ca1fe9378f75b1f577529270 hunk ./ApiUpdateTodoList.txt 129 -*** TODO RecentChooser.chs +*** DONE RecentChooser.chs hunk ./ApiUpdateTodoList.txt 136 -*** TODO RecentManager.chs +*** DONE RecentManager.chs hunk ./Makefile.am 654 + gtk/Graphics/UI/Gtk/General/IconTheme.chs.pp \ + gtk/Graphics/UI/Gtk/General/IconInfo.chs.pp \ hunk ./gtk/Graphics/UI/Gtk.hs.pp 45 + module Graphics.UI.Gtk.General.IconTheme, + module Graphics.UI.Gtk.General.IconInfo, hunk ./gtk/Graphics/UI/Gtk.hs.pp 266 +import Graphics.UI.Gtk.General.IconTheme +import Graphics.UI.Gtk.General.IconInfo addfile ./gtk/Graphics/UI/Gtk/General/IconInfo.chs.pp hunk ./gtk/Graphics/UI/Gtk/General/IconInfo.chs.pp 1 +{-# LANGUAGE ScopedTypeVariables #-} +-- -*-haskell-*- +-- GIMP Toolkit (GTK) Widget IconInfo +-- +-- Author : Andy Stewart +-- +-- Created: 28 Mar 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 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 : gtk...@li... +-- Stability : provisional +-- Portability : portable (depends on GHC) +-- +-- +module Graphics.UI.Gtk.General.IconInfo ( + +-- * Types + IconInfo, + mkIconInfo, + +-- * Constructors + iconInfoNewForPixbuf, + +-- * Methods + iconInfoCopy, + iconInfoFree, + -- iconInfoGetAttachPoints, + iconInfoGetBaseSize, + iconInfoGetBuiltinPixbuf, + iconInfoGetDisplayName, + iconInfoGetEmbeddedRect, + iconInfoGetFilename, + iconInfoLoadIcon, + iconInfoSetRawCoordinates, + ) where + +import Control.Monad (liftM) + +import System.Glib.FFI +import System.Glib.Attributes +import System.Glib.Properties +import System.Glib.UTFString +import Graphics.UI.Gtk.General.Structs (Rectangle, Point) +import System.Glib.GError (GErrorDomain, GErrorClass(..), propagateGError) +{#import Graphics.UI.Gtk.Types#} + +{# context lib="gtk" prefix="gtk" #} + +-------------------- +-- Types +{#pointer *IconInfo foreign newtype#} + +-- | Helper function for build 'IconInfo' +mkIconInfo :: Ptr IconInfo -> IO IconInfo +mkIconInfo info = liftM IconInfo $ newForeignPtr_ info + +-------------------- +-- Constructors + +-- | +-- +iconInfoNewForPixbuf :: IconThemeClass iconTheme => iconTheme -> Pixbuf -> IO IconInfo +iconInfoNewForPixbuf iconTheme pixbuf = do + iiPtr <- {# call gtk_icon_info_new_for_pixbuf #} + (toIconTheme iconTheme) + pixbuf + liftM IconInfo (newForeignPtr_ iiPtr) + +-------------------- +-- Methods + +-- | +-- +iconInfoCopy :: IconInfo -> IO IconInfo +iconInfoCopy self = do + iiPtr <- {# call gtk_icon_info_copy #} self + liftM IconInfo (newForeignPtr_ iiPtr) + +-- | Free a 'IconInfo' and associated information +iconInfoFree :: IconInfo -> IO () +iconInfoFree self = + {# call gtk_icon_info_free #} + self + +-- | +-- +-- iconInfoGetAttachPoints :: IconInfo -> IO (Maybe ([Point], Int)) +-- iconInfoGetAttachPoints self = +-- alloca $ \nPointsPtr -> +-- allocaArray 0 $ \pointPtr -> do +-- -- alloca $ \ (pointPtr :: Ptr (Ptr Point)) -> do +-- success <- liftM toBool $ [_$_] +-- {# call gtk_icon_info_get_attach_points #} +-- self +-- pointPtr +-- nPointsPtr +-- if success [_$_] +-- then do +-- nPoints <- peek nPointsPtr +-- pointList <- peekArray 0 (castPtr pointPtr :: Ptr (Ptr Point)) +-- return (Just (pointList, (fromIntegral nPoints))) +-- else return Nothing + +-- | Gets the base size for the icon. The base size is a size for the icon that was specified by the icon +-- theme creator. This may be different than the actual size of image; an example of this is small +-- emblem icons that can be attached to a larger icon. These icons will be given the same base size as +-- the larger icons to which they are attached. +-- [_$_] +iconInfoGetBaseSize :: IconInfo -> IO Int +iconInfoGetBaseSize self = + liftM fromIntegral $ + {# call gtk_icon_info_get_base_size #} + self + +-- | Gets the built-in image for this icon, if any. To allow GTK+ to use built in icon images, you must +-- pass the ''IconLookupUseBuiltin'' to 'iconThemeLookupIcon'. +iconInfoGetBuiltinPixbuf :: IconInfo -> IO Pixbuf +iconInfoGetBuiltinPixbuf self = + makeNewGObject mkPixbuf $ + {# call gtk_icon_info_get_builtin_pixbuf #} + self + +-- | Gets the display name for an icon. A display name is a string to be used in place of the icon name +-- in a user visible context like a list of icons. +iconInfoGetDisplayName :: IconInfo -> IO String +iconInfoGetDisplayName self = + {# call gtk_icon_info_get_display_name #} + self + >>= peekUTFString + +-- | Gets the coordinates of a rectangle within the icon that can be used for display of information such +-- as a preview of the contents of a text file. See 'iconInfoSetRawCoordinates' for further +-- information about the coordinate system. +iconInfoGetEmbeddedRect :: IconInfo -> Rectangle -> IO Bool +iconInfoGetEmbeddedRect self rectangle = + liftM toBool $ + with rectangle $ \ rectanglePtr -> [_$_] + {# call gtk_icon_info_get_embedded_rect #} + self + (castPtr rectanglePtr) + +-- | Gets the filename for the icon. If the ''IconLookupUseBuiltin'' flag was passed to +-- 'iconThemeLookupIcon', there may be no filename if a builtin icon is returned; in this case, +-- you should use 'iconInfoGetBuiltinPixbuf'. +iconInfoGetFilename :: IconInfo -> IO String +iconInfoGetFilename self = + {# call gtk_icon_info_get_filename #} + self + >>= peekUTFString + +-- | Looks up an icon in an icon theme, scales it to the given size and renders it into a pixbuf. This is +-- a convenience function; if more details about the icon are needed, use 'iconThemeLookupIcon' +-- followed by 'iconInfoLoadIcon'. +-- [_$_] +-- Note that you probably want to listen for icon theme changes and update the icon. This is usually +-- done by connecting to the 'styleSet' signal. If for some reason you do not want to update +-- the icon when the icon theme changes, you should consider using 'pixbufCopy' to make a private +-- copy of the pixbuf returned by this function. Otherwise GTK+ may need to keep the old icon theme +-- loaded, which would be a waste of memory. +iconInfoLoadIcon :: IconInfo -> IO Pixbuf +iconInfoLoadIcon self = + makeNewGObject mkPixbuf $ + propagateGError $ \errorPtr -> + {# call gtk_icon_info_load_icon #} + self + errorPtr + +-- | Sets whether the coordinates returned by 'iconInfoGetEmbeddedRect' and +-- 'iconInfoGetAttachPoints' should be returned in their original form as specified in the icon +-- theme, instead of scaled appropriately for the pixbuf returned by 'iconInfoLoadIcon'. +-- [_$_] +-- Raw coordinates are somewhat strange; they are specified to be with respect to the unscaled pixmap +-- for PNG and XPM icons, but for SVG icons, they are in a 1000x1000 coordinate space that is scaled to +-- the final size of the icon. You can determine if the icon is an SVG icon by using +-- 'iconInfoGetFilename', and seeing if it is non-'Nothing' and ends in '.svg'. +-- [_$_] +-- This function is provided primarily to allow compatibility wrappers for older API's, and is not +-- expected to be useful for applications. +iconInfoSetRawCoordinates :: IconInfo -> Bool -> IO () +iconInfoSetRawCoordinates self rawCoordinates = + {# call gtk_icon_info_set_raw_coordinates #} + self + (fromBool rawCoordinates) addfile ./gtk/Graphics/UI/Gtk/General/IconTheme.chs.pp hunk ./gtk/Graphics/UI/Gtk/General/IconTheme.chs.pp 1 +-- -*-haskell-*- +-- GIMP Toolkit (GTK) Widget IconTheme +-- +-- Author : Andy Stewart +-- +-- Created: 28 Mar 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 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 : gtk...@li... +-- Stability : provisional +-- Portability : portable (depends on GHC) +-- +-- Looking up icons by name +-- +-- * Module available since Gtk+ version 2.4 +-- +module Graphics.UI.Gtk.General.IconTheme ( + +-- * Detail +-- +-- | 'IconTheme' provides a facility for looking up icons by name and size. The main reason for using a +-- name rather than simply providing a filename is to allow different icons to be used depending on +-- what icon theme is selecetd by the user. The operation of icon themes on Linux and Unix follows the +-- Icon Theme Specification. There is a default icon theme, named hicolor where applications should +-- install their icons, but more additional application themes can be installed as operating system +-- vendors and users choose. +-- [_$_] +-- Named icons are similar to the Themeable Stock Images(3) facility, and the distinction between the +-- two may be a bit confusing. A few things to keep in mind: +-- [_$_] +-- [_\e2_][_\97_][_\8f_] Stock images usually are used in conjunction with Stock Items(3)., such as ''StockOk'' or +-- ''StockOpen''. Named icons are easier to set up and therefore are more useful for new icons +-- that an application wants to add, such as application icons or window icons. +-- [_$_] +-- [_\e2_][_\97_][_\8f_] Stock images can only be loaded at the symbolic sizes defined by the 'IconSize' enumeration, or +-- by custom sizes defined by 'iconSizeRegister', while named icons are more flexible and any +-- pixel size can be specified. +-- [_$_] +-- [_\e2_][_\97_][_\8f_] Because stock images are closely tied to stock items, and thus to actions in the user interface, +-- stock images may come in multiple variants for different widget states or writing directions. +-- [_$_] +-- A good rule of thumb is that if there is a stock image for what you want to use, use it, otherwise +-- use a named icon. It turns out that internally stock images are generally defined in terms of one or +-- more named icons. (An example of the more than one case is icons that depend on writing direction; +-- ''StockGoForward'' uses the two themed icons 'gtkStockGoForwardLtr' and +-- 'gtkStockGoForwardRtl'.) +-- [_$_] +-- In many cases, named themes are used indirectly, via 'Image' or stock items, rather than directly, +-- but looking up icons directly is also simple. The 'IconTheme' object acts as a database of all the +-- icons in the current theme. You can create new 'IconTheme' objects, but its much more efficient to +-- use the standard icon theme for the 'Screen' so that the icon information is shared with other +-- people looking up icons. In the case where the default screen is being used, looking up an icon can +-- be as simple as: +-- +-- * Class Hierarchy +-- +-- | +-- @ +-- | 'GObject' +-- | +----IconTheme +-- @ + +#if GTK_CHECK_VERSION(2,4,0) +-- * Types + IconTheme, + IconThemeClass, + castToIconTheme, + toIconTheme, + +-- * Enums + IconLookupFlags(..), + IconThemeError(..), + +-- * Constructors + iconThemeNew, + +-- * Methods + iconThemeGetDefault, + iconThemeGetForScreen, + iconThemeSetScreen, + iconThemeSetSearchPath, + iconThemeGetSearchPath, + iconThemeAppendSearchPath, + iconThemePrependSearchPath, + iconThemeSetCustomTheme, + iconThemeHasIcon, + iconThemeLookupIcon, +#if GTK_CHECK_VERSION(2,12,0) + iconThemeChooseIcon, +#if GTK_CHECK_VERSION(2,14,0) + -- iconThemeLookupByGicon, +#endif +#endif + iconThemeLoadIcon, +#if GTK_CHECK_VERSION(2,12,0) + iconThemeListContexts, +#endif + iconThemeListIcons, +#if GTK_CHECK_VERSION(2,6,0) + iconThemeGetIconSizes, +#endif + iconThemeGetExampleIconName, + iconThemeRescanIfNeeded, + iconThemeAddBuiltinIcon, + iconThemeErrorQuark, + +-- * Signals + iconThemeChanged, +#endif + ) where + +import Control.Monad (liftM) + +import System.Glib.FFI +import System.Glib.Attributes +import System.Glib.Properties +import System.Glib.UTFString +import System.Glib.GList +import System.Glib.Flags +import System.Glib.GObject (constructNewGObject, makeNewGObject, Quark) +import System.Glib.GError (GErrorDomain, GErrorClass(..), propagateGError) +import Graphics.UI.Gtk.General.IconInfo (IconInfo, mkIconInfo) +{#import Graphics.UI.Gtk.Types#} +{#import Graphics.UI.Gtk.Signals#} + +{# context lib="gtk" prefix="gtk" #} + +#if GTK_CHECK_VERSION(2,4,0) +-------------------- +-- Enums +{#enum IconLookupFlags {underscoreToCase} deriving (Bounded,Eq,Show)#} + +{#enum IconThemeError {underscoreToCase} deriving (Bounded,Eq,Show)#} + +-------------------- +-- Constructors + +-- | Creates a new icon theme object. Icon theme objects are used to lookup up +-- an icon by name in a particular icon theme. Usually, you'll want to use +-- 'iconThemeGetDefault' or 'iconThemeGetForScreen' rather than creating a new +-- icon theme object for scratch. +-- +iconThemeNew :: IO IconTheme +iconThemeNew = + constructNewGObject mkIconTheme $ + {# call gtk_icon_theme_new #} + +-------------------- +-- Methods + +-- | Gets the icon theme for the default screen. See 'iconThemeGetForScreen'. +-- +iconThemeGetDefault :: + IO IconTheme -- ^ returns A unique 'IconTheme' associated with the default + -- screen. This icon theme is associated with the screen and + -- can be used as long as the screen is open. Do not ref or + -- unref it. +iconThemeGetDefault = + makeNewGObject mkIconTheme $ + {# call gtk_icon_theme_get_default #} + +-- | Gets the icon theme object associated with @screen@; if this function has +-- not previously been called for the given screen, a new icon theme object +-- will be created and associated with the screen. Icon theme objects are +-- fairly expensive to create, so using this function is usually a better +-- choice than calling than 'iconThemeNew' and setting the screen yourself; by +-- using this function a single icon theme object will be shared between users. +-- +iconThemeGetForScreen :: + Screen -- ^ @screen@ - a 'Screen' + -> IO IconTheme -- ^ returns A unique 'IconTheme' associated with the given + -- screen. This icon theme is associated with the screen and + -- can be used as long as the screen is open. Do not ref or + -- unref it. +iconThemeGetForScreen screen = + makeNewGObject mkIconTheme $ + {# call gtk_icon_theme_get_for_screen #} + screen + +-- | Sets the screen for an icon theme; the screen is used to track the user's +-- currently configured icon theme, which might be different for different +-- screens. +-- +iconThemeSetScreen :: IconThemeClass self => self + -> Screen -- ^ @screen@ - a 'Screen' + -> IO () +iconThemeSetScreen self screen = + {# call gtk_icon_theme_set_screen #} + (toIconTheme self) + screen + +-- | Sets the search path for the icon theme object. When looking for an icon +-- theme, Gtk+ will search for a subdirectory of one or more of the directories +-- in @path@ with the same name as the icon theme. (Themes from multiple of the +-- path elements are combined to allow themes to be extended by adding icons in +-- the user's home directory.) +-- +-- In addition if an icon found isn't found either in the current icon theme +-- or the default icon theme, and an image file with the right name is found +-- directly in one of the elements of @path@, then that image will be used for +-- the icon name. (This is legacy feature, and new icons should be put into the +-- default icon theme, which is called DEFAULT_THEME_NAME, rather than directly +-- on the icon path.) +-- +iconThemeSetSearchPath :: IconThemeClass self => self + -> [String] -- ^ @path@ - array of directories that are searched for icon + -- themes + -> Int -- ^ @nElements@ - number of elements in @path@. + -> IO () +iconThemeSetSearchPath self path nElements = + withUTFStringArray path $ \pathPtr -> + {# call gtk_icon_theme_set_search_path #} + (toIconTheme self) + pathPtr + (fromIntegral nElements) + +-- | Gets the current search path. See 'iconThemeSetSearchPath'. +-- +iconThemeGetSearchPath :: IconThemeClass self => self + -> IO ([String], Int) -- ^ @(path, nElements)@ [_$_] + -- @path@ - location to store a list of icon theme path + -- directories. The stored value should + -- be freed with 'gStrfreev'. @nElements@ - location to + -- store number of elements in @path@ +iconThemeGetSearchPath self = + alloca $ \nElementsPtr -> [_$_] + allocaArray 0 $ \pathPtr -> do + {# call gtk_icon_theme_get_search_path #} + (toIconTheme self) + pathPtr + nElementsPtr + list <- peekArray 0 pathPtr + pathList <- mapM (peekArray 0) list + pathStr <- mapM peekCString (concat pathList) + nElements <- peek nElementsPtr + return (pathStr, fromIntegral nElements) + +-- | Appends a directory to the search path. See 'iconThemeSetSearchPath'. +-- +iconThemeAppendSearchPath :: IconThemeClass self => self + -> String -- ^ @path@ - directory name to append to the icon path + -> IO () +iconThemeAppendSearchPath self path = + withUTFString path $ \pathPtr -> + {# call gtk_icon_theme_append_search_path #} + (toIconTheme self) + pathPtr + +-- | Prepends a directory to the search path. See 'iconThemeSetSearchPath'. +-- +iconThemePrependSearchPath :: IconThemeClass self => self + -> String -- ^ @path@ - directory name to prepend to the icon path + -> IO () +iconThemePrependSearchPath self path = + withUTFString path $ \pathPtr -> + {# call gtk_icon_theme_prepend_search_path #} + (toIconTheme self) + pathPtr + +-- | Sets the name of the icon theme that the 'IconTheme' object uses +-- overriding system configuration. This function cannot be called on the icon +-- theme objects returned from 'iconThemeGetDefault' and +-- 'iconThemeGetForScreen'. +-- +iconThemeSetCustomTheme :: IconThemeClass self => self + -> String -- ^ @themeName@ - name of icon theme to use instead of configured + -- theme + -> IO () +iconThemeSetCustomTheme self themeName = + withUTFString themeName $ \themeNamePtr -> + {# call gtk_icon_theme_set_custom_theme #} + (toIconTheme self) + themeNamePtr + +-- | Checks whether an icon theme includes an icon for a particular name. +-- +iconThemeHasIcon :: IconThemeClass self => self + -> String -- ^ @iconName@ - the name of an icon + -> IO Bool -- ^ returns @True@ if @iconTheme@ includes an icon for + -- @iconName@. +iconThemeHasIcon self iconName = + liftM toBool $ + withUTFString iconName $ \iconNamePtr -> + {# call gtk_icon_theme_has_icon #} + (toIconTheme self) + iconNamePtr + +-- | Looks up a named icon and returns a structure containing information such +-- as the filename of the icon. The icon can then be rendered into a pixbuf +-- using 'iconInfoLoadIcon'. ('iconThemeLoadIcon' combines these two steps if +-- all you need is the pixbuf.) +-- +iconThemeLookupIcon :: IconThemeClass self => self + -> String -- ^ @iconName@ - the name of the icon to lookup + -> Int -- ^ @size@ - desired icon size + -> IconLookupFlags -- ^ @flags@ - flags modifying the behavior of the + -- icon lookup + -> IO (Maybe IconInfo) -- ^ returns a 'IconInfo' + -- structure containing information about the icon, or + -- 'Nothing' if the icon wasn't found. Free + -- with 'iconInfoFree' +iconThemeLookupIcon self iconName size flags = + withUTFString iconName $ \iconNamePtr -> do + iiPtr <- {# call gtk_icon_theme_lookup_icon #} + (toIconTheme self) + iconNamePtr + (fromIntegral size) + ((fromIntegral . fromEnum) flags) + if iiPtr == nullPtr [_$_] + then return Nothing + else liftM Just (mkIconInfo (castPtr iiPtr)) + +#if GTK_CHECK_VERSION(2,12,0) +-- | Looks up a named icon and returns a structure containing information such +-- as the filename of the icon. The icon can then be rendered into a pixbuf +-- using 'iconInfoLoadIcon'. ('iconThemeLoadIcon' combines these two steps if +-- all you need is the pixbuf.) +-- +-- If @iconNames@ contains more than one name, this function tries them all +-- in the given order before falling back to inherited icon themes. +-- +-- * Available since Gtk+ version 2.12 +-- +iconThemeChooseIcon :: IconThemeClass self => self + -> [String] -- ^ @iconNames@ terminated array of icon names to lookup + -> Int -- ^ @size@ - desired icon size + -> IconLookupFlags -- ^ @flags@ - flags modifying the behavior of the + -- icon lookup + -> IO (Maybe IconInfo) -- ^ returns a 'IconInfo' + -- structure containing information about the icon, or + -- 'Nothing' if the icon wasn't found. Free + -- with 'iconInfoFree' +iconThemeChooseIcon self iconNames size flags = + withUTFStringArray iconNames $ \iconNamesPtr -> do + iiPtr <- {# call gtk_icon_theme_choose_icon #} + (toIconTheme self) + iconNamesPtr + (fromIntegral size) + ((fromIntegral . fromEnum) flags) + if iiPtr == nullPtr [_$_] + then return Nothing + else liftM Just (mkIconInfo (castPtr iiPtr)) + +#if GTK_CHECK_VERSION(2,14,0) +-- | Looks up an icon and returns a structure containing information such as +-- the filename of the icon. The icon can then be rendered into a pixbuf using +-- 'iconInfoLoadIcon'. +-- +-- * Available since Gtk+ version 2.14 +-- +-- iconThemeLookupByGicon :: IconThemeClass self => self +-- -> {-GIcon*-} -- ^ @icon@ - the {GIcon, FIXME: unknown type\/value} +-- -- to look up +-- -> Int -- ^ @size@ - desired icon size +-- -> [IconLookupFlags] -- ^ @flags@ - flags modifying the behavior of the +-- -- icon lookup +-- -> IO IconInfo -- ^ returns a 'IconInfo' +-- -- structure containing information about the icon, or +-- -- {@NULL@, FIXME: this should probably be converted to +-- -- a Maybe data type} if the icon wasn't found. Free +-- -- with 'iconInfoFree' +-- iconThemeLookupByGicon self icon size flags = +-- {# call gtk_icon_theme_lookup_by_gicon #} +-- (toIconTheme self) +-- {-icon-} +-- (fromIntegral size) +-- ((fromIntegral . fromFlags) flags) +#endif +#endif + +-- | Looks up an icon in an icon theme, scales it to the given size and +-- renders it into a pixbuf. This is a convenience function; if more details +-- about the icon are needed, use 'iconThemeLookupIcon' followed by +-- 'iconInfoLoadIcon'. +-- +-- Note that you probably want to listen for icon theme changes and update +-- the icon. This is usually done by connecting to the 'Widget'::style-set +-- signal. If for some reason you do not want to update the icon when the icon +-- theme changes, you should consider using 'pixbufCopy' to make a private copy +-- of the pixbuf returned by this function. Otherwise Gtk+ may need to keep the +-- old icon theme loaded, which would be a waste of memory. +-- +iconThemeLoadIcon :: IconThemeClass self => self + -> String -- ^ @iconName@ - the name of the icon to lookup + -> Int -- ^ @size@ - the desired icon size. The resulting icon + -- may not be exactly this size; see 'iconInfoLoadIcon'. + -> IconLookupFlags -- ^ @flags@ - flags modifying the behavior of the icon + -- lookup + -> IO Pixbuf -- ^ returns the rendered icon; this may be a newly + -- created icon or a new reference to an internal icon, + -- so you must not modify the icon. Use 'gObjectUnref' to + -- release your reference to the icon +iconThemeLoadIcon self iconName size flags = + makeNewGObject mkPixbuf $ + propagateGError $ \errorPtr -> + withUTFString iconName $ \iconNamePtr -> + {# call gtk_icon_theme_load_icon #} + (toIconTheme self) + iconNamePtr + (fromIntegral size) + ((fromIntegral . fromEnum) flags) + errorPtr + +#if GTK_CHECK_VERSION(2,12,0) +-- | Gets the list of contexts available within the current hierarchy of icon +-- themes +-- +-- * Available since Gtk+ version 2.12 +-- +iconThemeListContexts :: IconThemeClass self => self + -> IO [String] -- ^ returns a String list + -- holding the names of all the contexts in the + -- theme. You must first free each element in the + -- list with 'gFree', then free the list itself + -- with 'gListFree'. +iconThemeListContexts self = do + glist <- {# call gtk_icon_theme_list_contexts #} (toIconTheme self) + list <- fromGList glist + mapM (\strPtr -> do str <- peekUTFString strPtr + {# call unsafe g_free #} (castPtr strPtr) + return str) list [_$_] +#endif + +-- | Lists the icons in the current icon theme. Only a subset of the icons can +-- be listed by providing a context string. The set of values for the context +-- string is system dependent, but will typically include such values as +-- \"Applications\" and \"MimeTypes\". +-- +iconThemeListIcons :: IconThemeClass self => self + -> String -- ^ @context@ - a string identifying a particular + -- type of icon + -> IO [String] -- ^ returns a String list + -- holding the names of all the icons in the theme. + -- You must first free each element in the list + -- with 'gFree', then free the list itself with + -- 'gListFree'. +iconThemeListIcons self context = + withUTFString context $ \contextPtr -> do + glist <- {# call gtk_icon_theme_list_icons #} + (toIconTheme self) + contextPtr + list <- fromGList glist + mapM (\strPtr -> do str <- peekUTFString strPtr + {# call unsafe g_free #} (castPtr strPtr) + return str) list [_$_] + +#if GTK_CHECK_VERSION(2,6,0) +-- | Returns an array of integers describing the sizes at which the icon is +-- available without scaling. A size of -1 means that the icon is available in +-- a scalable format. The array is zero-terminated. +-- +-- * Available since Gtk+ version 2.6 +-- +iconThemeGetIconSizes :: IconThemeClass self => self + -> String -- ^ @iconName@ - the name of an icon + -> IO [Int] -- ^ returns An newly allocated array describing the sizes at + -- which the icon is available. The array should be freed with + -- 'gFree' when it is no longer needed. +iconThemeGetIconSizes self iconName = + withUTFString iconName $ \iconNamePtr -> do + listPtr <- {# call gtk_icon_theme_get_icon_sizes #} + (toIconTheme self) + iconNamePtr + list <- peekArray 0 listPtr + return (map fromIntegral list) +#endif + +-- | Gets the name of an icon that is representative of the current theme (for +-- instance, to use when presenting a list of themes to the user.) +-- +iconThemeGetExampleIconName :: IconThemeClass self => self + -> IO String -- ^ returns the name of an example icon [_$_] +iconThemeGetExampleIconName self = + {# call gtk_icon_theme_get_example_icon_name #} + (toIconTheme self) + >>= readUTFString + +-- | Checks to see if the icon theme has changed; if it has, any currently +-- cached information is discarded and will be reloaded next time @iconTheme@ +-- is accessed. +-- +iconThemeRescanIfNeeded :: IconThemeClass self => self + -> IO Bool -- ^ returns @True@ if the icon theme has changed and needed to be + -- reloaded. +iconThemeRescanIfNeeded self = + liftM toBool $ + {# call gtk_icon_theme_rescan_if_needed #} + (toIconTheme self) + +-- | Registers a built-in icon for icon theme lookups. The idea of built-in +-- icons is to allow an application or library that uses themed icons to +-- function requiring files to be present in the file system. For instance, the +-- default images for all of Gtk+'s stock icons are registered as built-icons. +-- +-- In general, if you use 'iconThemeAddBuiltinIcon' you should also install +-- the icon in the icon theme, so that the icon is generally available. +-- +-- This function will generally be used with pixbufs loaded via +-- 'pixbufNewFromInline'. +-- +iconThemeAddBuiltinIcon :: + String -- ^ @iconName@ - the name of the icon to register + -> Int -- ^ @size@ - the size at which to register the icon (different + -- images can be registered for the same icon name at different + -- sizes.) + -> Pixbuf -- ^ @pixbuf@ - 'Pixbuf' that contains the image to use for + -- @iconName@. + -> IO () +iconThemeAddBuiltinIcon iconName size pixbuf = + withUTFString iconName $ \iconNamePtr -> + {# call gtk_icon_theme_add_builtin_icon #} + iconNamePtr + (fromIntegral size) + pixbuf + +-- | +-- +iconThemeErrorQuark :: IO Quark +iconThemeErrorQuark = + {# call gtk_icon_theme_error_quark #} + +-------------------- +-- Signals + +-- | Emitted when the current icon theme is switched or Gtk+ detects that a +-- change has occurred in the contents of the current icon theme. +-- +iconThemeChanged :: IconThemeClass self => Signal self (IO ()) +iconThemeChanged = Signal (connect_NONE__NONE "changed") + +#endif hunk ./gtk/Graphics/UI/Gtk/Recent/RecentChooser.chs.pp 80 - -- recentChooserSetSortFunc, + recentChooserSetSortFunc, hunk ./gtk/Graphics/UI/Gtk/Recent/RecentChooser.chs.pp 83 - -- recentChooserGetCurrentItem, + recentChooserGetCurrentItem, hunk ./gtk/Graphics/UI/Gtk/Recent/RecentChooser.chs.pp 88 - -- recentChooserGetItems, + recentChooserGetItems, hunk ./gtk/Graphics/UI/Gtk/Recent/RecentChooser.chs.pp 122 -{#import Graphics.UI.Gtk.Recent.RecentInfo#} (RecentInfo) +{#import Graphics.UI.Gtk.Recent.RecentInfo#} (RecentInfo, mkRecentInfo) hunk ./gtk/Graphics/UI/Gtk/Recent/RecentChooser.chs.pp 146 --- recentChooserSetSortFunc :: RecentChooserClass self => self --- -> (Maybe (RecentInfo -> IO Int)) --- -> IO () --- recentChooserSetSortFunc self Nothing = --- {# call gtk_recent_chooser_set_sort_func #} --- (toRecentChooser self) nullFunPtr nullPtr nullFunPtr --- recentChooserSetSortFunc self (Just func) = do --- fPtr <- mkRecentSortFunc $ \_ info _ -> func info --- {# call gtk_recent_chooser_set_sort_func #} --- (toRecentChooser self) --- fPtr --- (castFunPtrToPtr fPtr) --- destroyFunPtr +recentChooserSetSortFunc :: RecentChooserClass self => self + -> (Maybe (RecentInfo -> IO Int)) + -> IO () +recentChooserSetSortFunc self Nothing = + {# call gtk_recent_chooser_set_sort_func #} + (toRecentChooser self) nullFunPtr nullPtr nullFunPtr +recentChooserSetSortFunc self (Just func) = do + fPtr <- mkRecentSortFunc $ \_ infoPtr _ -> do + info <- mkRecentInfo infoPtr + liftM fromIntegral (func info) + {# call gtk_recent_chooser_set_sort_func #} + (toRecentChooser self) + fPtr + (castFunPtrToPtr fPtr) + destroyFunPtr hunk ./gtk/Graphics/UI/Gtk/Recent/RecentChooser.chs.pp 194 --- recentChooserGetCurrentItem :: RecentChooserClass self => self --- -> IO RecentInfo -- ^ returns a 'RecentInfo'. --- -- Use 'recentInfoUnref' when when you have finished --- -- using it. --- recentChooserGetCurrentItem self = --- {# call gtk_recent_chooser_get_current_item #} --- (toRecentChooser self) +recentChooserGetCurrentItem :: RecentChooserClass self => self + -> IO RecentInfo -- ^ returns a 'RecentInfo'. + -- Use 'recentInfoUnref' when when you have finished + -- using it. +recentChooserGetCurrentItem self = do + info <- {# call gtk_recent_chooser_get_current_item #} (toRecentChooser self) + mkRecentInfo info hunk ./gtk/Graphics/UI/Gtk/Recent/RecentChooser.chs.pp 247 --- recentChooserGetItems :: RecentChooserClass self => self --- -> IO [RecentInfo] -- ^ returns A newly allocated list of --- -- 'RecentInfo' objects. You --- -- should use 'recentInfoUnref' on every item of --- -- the list, and then free the list itself using --- -- 'gListFree'. --- recentChooserGetItems self = --- {# call gtk_recent_chooser_get_items #} --- (toRecentChooser self) --- >>= fromGList - -- >>= mapM (\elemPtr -> RecentInfo elemPtr) +recentChooserGetItems :: RecentChooserClass self => self + -> IO [RecentInfo] -- ^ returns A newly allocated list of + -- 'RecentInfo' objects. You + -- should use 'recentInfoUnref' on every item of + -- the list, and then free the list itself using + -- 'gListFree'. +recentChooserGetItems self = do + glist <- {# call gtk_recent_chooser_get_items #} (toRecentChooser self) + list <- fromGList glist + mapM mkRecentInfo list hunk ./gtk/Graphics/UI/Gtk/Recent/RecentInfo.chs.pp 30 + mkRecentInfo, hunk ./gtk/Graphics/UI/Gtk/Recent/RecentInfo.chs.pp 73 +-- | Helper function for build 'RecentInfo' +mkRecentInfo :: Ptr RecentInfo -> IO RecentInfo +mkRecentInfo info = liftM RecentInfo $ newForeignPtr_ info + hunk ./gtk/Graphics/UI/Gtk/Recent/RecentManager.chs.pp 73 - -- recentManagerLookupItem, + recentManagerLookupItem, hunk ./gtk/Graphics/UI/Gtk/Recent/RecentManager.chs.pp 76 - -- recentManagerGetItems, + recentManagerGetItems, hunk ./gtk/Graphics/UI/Gtk/Recent/RecentManager.chs.pp 99 -{#import Graphics.UI.Gtk.Recent.RecentInfo#} (RecentInfo) +{#import Graphics.UI.Gtk.Recent.RecentInfo#} (RecentInfo, mkRecentInfo) hunk ./gtk/Graphics/UI/Gtk/Recent/RecentManager.chs.pp 209 --- recentManagerLookupItem :: RecentManagerClass self => self --- -> String -- ^ @uri@ - a URI --- -> IO RecentInfo -- ^ returns a 'RecentInfo' --- -- structure containing information about the --- -- resource pointed by @uri@, or {@NULL@, FIXME: this --- -- should probably be converted to a Maybe data type} --- -- if the URI was not registered in the recently used --- -- resources list. Free with 'recentInfoUnref'. --- recentManagerLookupItem self uri = --- propagateGError $ \errorPtr -> --- withUTFString uri $ \uriPtr -> do --- result <- {# call unsafe gtk_recent_manager_lookup_item #} --- (toRecentManager self) --- uriPtr --- errorPtr --- makeNewRecentInfo result +recentManagerLookupItem :: RecentManagerClass self => self + -> String -- ^ @uri@ - a URI + -> IO RecentInfo -- ^ returns a 'RecentInfo' + -- structure containing information about the + -- resource pointed by @uri@, or {@NULL@, FIXME: this + -- should probably be converted to a Maybe data type} + -- if the URI was not registered in the recently used + -- resources list. Free with 'recentInfoUnref'. +recentManagerLookupItem self uri = + propagateGError $ \errorPtr -> + withUTFString uri $ \uriPtr -> do + result <- {# call unsafe gtk_recent_manager_lookup_item #} + (toRecentManager self) + uriPtr + errorPtr + mkRecentInfo result hunk ./gtk/Graphics/UI/Gtk/Recent/RecentManager.chs.pp 261 --- recentManagerGetItems :: RecentManagerClass self => self --- -> IO [RecentInfo] -- ^ returns a list of newly allocated --- -- 'RecentInfo' objects. Use --- -- 'recentInfoUnref' on each item inside the list, --- -- and then free the list itself using 'gListFree'. --- recentManagerGetItems self = do --- glist <- {# call gtk_recent_manager_get_items #} --- (toRecentManager self) --- list <- fromGList glist --- return list +recentManagerGetItems :: RecentManagerClass self => self + -> IO [RecentInfo] -- ^ returns a list of newly allocated + -- 'RecentInfo' objects. Use + -- 'recentInfoUnref' on each item inside the list, + -- and then free the list itself using 'gListFree'. +recentManagerGetItems self = do + glist <- {# call gtk_recent_manager_get_items #} + (toRecentManager self) + list <- fromGList glist + mapM mkRecentInfo list hunk ./gtk/Graphics/UI/Gtk/Special/Ruler.chs.pp 117 - -- maxSize)@ {FIXME: merge return value - -- docs} @lower@ - location to store - -- lower limit of the ruler, or - -- {@NULL@, FIXME: this should probably - -- be converted to a Maybe data - -- type}@upper@ - location to store - -- upper limit of the ruler, or - -- {@NULL@, FIXME: this should probably - -- be converted to a Maybe data - -- type}@position@ - location to store + -- maxSize)@ @loewr@ - location to store + -- lower limit of the ruler + -- @upper@ - location to store + -- upper limit of the ruler, [_$_] + -- @position@ - location to store hunk ./gtk/Graphics/UI/Gtk/Special/Ruler.chs.pp 123 - -- the ruler, or {@NULL@, FIXME: this - -- should probably be converted to a - -- Maybe data type}@maxSize@ - location + -- the ruler, [_$_] + -- @maxSize@ - location hunk ./gtk/Graphics/UI/Gtk/Special/Ruler.chs.pp 127 - -- space to leave for the text, or - -- {@NULL@, FIXME: this should probably - -- be converted to a Maybe data type}. + -- space to leave for the text + hunk ./gtk/Graphics/UI/Gtk/Special/Ruler.chs.pp 163 --- | --- +-- | Lower limit of ruler. +-- [_$_] +-- Default value: 0 hunk ./gtk/Graphics/UI/Gtk/Special/Ruler.chs.pp 169 --- | --- +-- | Upper limit of ruler. +-- [_$_] +-- Default value: 0 hunk ./gtk/Graphics/UI/Gtk/Special/Ruler.chs.pp 175 --- | --- +-- | Position of mark on the ruler. +-- [_$_] +-- Default value: 0 hunk ./gtk/Graphics/UI/Gtk/Special/Ruler.chs.pp 181 --- | --- +-- | Maximum size of the ruler. +-- [_$_] +-- Default value: 0 hunk ./gtk/Graphics/UI/Gtk/Special/Ruler.chs.pp 187 --- | --- +-- | The metric used for the ruler. +-- [_$_] +-- Default value: ''Pixels'' +-- [_$_] +-- Since 2.8 hunk ./tools/hierarchyGen/hierarchy.list 208 + GtkIconTheme |