Thu Aug 21 17:18:47 EDT 2008 A....@ke... * Revamp widget by adding most methods and separating signals from events. Keep only the old style signals with the mixture of events and signals that we had before in order not to break anything. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 8 --- Copyright (C) 2001-2005 Axel Simon +-- Copyright (C) 2001-2008 Axel Simon hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 20 --- TODO --- --- unimplemented methods that seem to be useful in user programs: --- widgetSizeRequest, widgetAddAccelerator, widgetRemoveAccelerator, --- widgetAcceleratorSignal, widgetGrabDefault, --- widgetPango*, widgetSetAdjustments --- --- implement the following methods in GtkWindow object: --- widget_set_uposition, widget_set_usize hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 26 --- The base class for all widgets. While a widget cannot be created directly, +-- The base class for all widgets. +-- +module Graphics.UI.Gtk.Abstract.Widget ( + +-- * Detail +-- +-- | The base class for all widgets. While a widget cannot be created directly, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 37 -module Graphics.UI.Gtk.Abstract.Widget ( --- * Detail --- [_$_] --- | 'Widget' introduces style properties - these are basically object +-- 'Widget' introduces style properties - these are basically object hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 43 +-- hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 50 +-- hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 64 - Allocation, + EventMask(..), + ExtensionMode(..), + GType, + KeyVal, + Region, + Bitmap, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 72 + Color, + IconSize(..), + StateType(..), + TextDirection(..), hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 78 - [_$_] + StockId, + WidgetHelpType(..), + hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 82 - widgetGetState, - widgetGetSavedState, - widgetShow, -- Showing and hiding a widget. + widgetShow, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 88 - widgetQueueDraw, -- Functions to be used with DrawingArea. - widgetGetDrawWindow, - widgetGetSize, - widgetHasIntersection, + widgetQueueDraw, + widgetAddAccelerator, + widgetRemoveAccelerator, + widgetSetAccelPath, +#if GTK_CHECK_VERSION(2,4,0) + widgetCanActivateAccel, +#endif + widgetActivate, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 97 - widgetRegionIntersect, - widgetActivate, -- Manipulate widget state. - widgetSetSensitivity, - widgetSetSizeRequest, - widgetGetSizeRequest, + widgetHasIntersection, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 99 - widgetSetAppPaintable, - widgetSetName, -- Naming, Themes + widgetGrabDefault, + widgetSetName, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 102 - EventMask(..), + widgetSetSensitive, + widgetSetSensitivity, + widgetGetParentWindow, + widgetGetDrawWindow, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 109 - ExtensionMode(..), + widgetSetEvents, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 112 - widgetGetToplevel, -- Widget browsing. - widgetIsAncestor, - widgetReparent, - TextDirection(..), - widgetSetDirection, -- General Setup. - widgetGetDirection, - widgetQueueDrawArea, - widgetSetDoubleBuffered, - widgetSetRedrawOnAllocate, - widgetGetParentWindow, + widgetGetToplevel, + widgetGetAncestor, + widgetGetColormap, + widgetSetColormap, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 117 + widgetIsAncestor, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 119 + widgetSetStyle, + widgetGetStyle, + widgetPushColormap, + widgetPopColormap, + widgetSetDefaultColormap, + widgetGetDefaultStyle, + widgetGetDefaultColormap, + widgetSetDirection, + widgetGetDirection, + widgetSetDefaultDirection, + widgetGetDefaultDirection, + widgetShapeCombineMask, +#if GTK_CHECK_VERSION(2,10,0) + widgetInputShapeCombineMask, +#endif hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 137 - widgetSetCompositeName, - widgetGetParent, - widgetSetDefaultDirection, - widgetGetDefaultDirection, - widgetGetStyle, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 144 - widgetCreateLayout, -- Drawing text. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 146 + widgetCreateLayout, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 148 + widgetQueueDrawArea, + widgetResetShapes, + widgetSetAppPaintable, + widgetSetDoubleBuffered, + widgetSetRedrawOnAllocate, + widgetSetCompositeName, + widgetSetScrollAdjustments, + widgetRegionIntersect, + widgetGetAccessible, + widgetChildFocus, + widgetGetChildVisible, + widgetGetParent, + widgetGetSettings, +#if GTK_CHECK_VERSION(2,2,0) + --widgetGetClipboard, + widgetGetDisplay, + widgetGetRootWindow, + widgetGetScreen, + widgetHasScreen, +#endif + widgetGetSizeRequest, + widgetSetChildVisible, + widgetSetSizeRequest, +#if GTK_CHECK_VERSION(2,4,0) + widgetSetNoShowAll, + widgetGetNoShowAll, + widgetListMnemonicLabels, + widgetAddMnemonicLabel, + widgetRemoveMnemonicLabel, +#if GTK_CHECK_VERSION(2,10,0) + widgetGetAction, + widgetIsComposited, +#endif +#endif + widgetReparent, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 185 - widgetGetColormap, - widgetSetColormap, - widgetGetScreen, + widgetGetState, + widgetGetSavedState, + widgetGetSize, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 208 + widgetChildVisible, + widgetColormap, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 212 - widgetSensitivity, hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 214 + realize, + unrealize, + mapSignal, + unmapSignal, + sizeRequest, + sizeAllocate, + showSignal, + hideSignal, + focus, + stateChanged, + parentSet, + hierarchyChanged, + styleSet, + directionChanged, + grabNotify, + popupMenuSignal, + showHelp, + accelClosuresChanged, + screenChanged, + +-- * Events + buttonPressEvent, + buttonReleaseEvent, + configureEvent, + deleteEvent, + destroyEvent, + enterNotifyEvent, + exposeEvent, + focusInEvent, + focusOutEvent, +#if GTK_CHECK_VERSION(2,8,0) + grabBrokenEvent, +#endif + keyPressEvent, + keyReleaseEvent, + leaveNotifyEvent, + mapEvent, + motionNotifyEvent, + noExposeEvent, + proximityInEvent, + proximityOutEvent, + scrollEvent, + unmapEvent, + visibilityNotifyEvent, + windowStateEvent, + +-- * Deprecated +#ifndef DISABLE_DEPRECATED hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 324 - StateType(..), hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 334 +#endif hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 340 +import Data.Bits ((.&.), complement) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 347 +import System.Glib.GType (GType) +import System.Glib.GList (GList, fromGList) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 353 +import Graphics.UI.Gtk.Gdk.Keys (KeyVal) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 355 +{#import Graphics.UI.Gtk.Gdk.Pixmap#} (Bitmap) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 357 - ,Requisition(..), Color, IconSize + ,Requisition(..), Color, IconSize(..) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 361 - marshExposeRect) + marshExposeRect, + EventButton, + EventScroll, + EventMotion, + EventExpose, + EventKey, + EventConfigure, + EventCrossing, + EventFocus, + EventProperty, + EventProximity, + EventVisibility, + EventWindowState, + EventGrabBroken) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 376 - AccelFlags(..), DirectionType(..)) + AccelFlags(..), DirectionType(..), Modifier) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 385 + hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 457 --- Functions to be used with DrawingArea. - --- | Prepare text for display. --- --- The 'PangoLayout' represents the rendered text. It can be shown on screen --- by calling 'Graphics.UI.Gtk.Gdk.Drawable.drawLayout'. --- --- The returned 'PangoLayout' shares the same font information ('PangoContext') as this --- widget. If this information changes, the 'PangoLayout' should change. The --- following code ensures that the displayed text always reflects the widget's --- settings: --- --- > l <- widgetCreateLayout w "My Text." --- > let update = do --- > layoutContextChanged l --- > -- update the Drawables which show this layout --- > w `onDirectionChanged` update --- > w `onStyleChanged` update --- -widgetCreateLayout :: WidgetClass self => self - -> String -- ^ @text@ - text to set on the layout - -> IO PangoLayout -widgetCreateLayout self text = do - pl <- constructNewGObject mkPangoLayoutRaw $ - withUTFString text $ \textPtr -> - {# call unsafe widget_create_pango_layout #} - (toWidget self) - textPtr - ps <- makeNewPangoString text - psRef <- newIORef ps - return (PangoLayout psRef pl) +-- * Functions to be used with 'Graphics.UI.Gtk.Misc.DrawingArea'. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 467 --- | Check if the widget intersects with a given area. +-- %hash c:1e14 d:53c5 +-- | Installs an accelerator for this @widget@ in @accelGroup@ that causes +-- @accelSignal@ to be emitted if the accelerator is activated. The +-- @accelGroup@ needs to be added to the widget's toplevel via +-- 'windowAddAccelGroup', and the signal must be of type @G_RUN_ACTION@. +-- Accelerators added through this function are not user changeable during +-- runtime. If you want to support accelerators that can be changed by the +-- user, use 'accelMapAddEntry' and 'widgetSetAccelPath' or +-- 'menuItemSetAccelPath' instead. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 477 -widgetHasIntersection :: WidgetClass self => self - -> Rectangle -- ^ @area@ - a rectangle - -> IO Bool -- ^ returns @True@ if there was an intersection -widgetHasIntersection self area = [_$_] - liftM toBool $ - with area $ \areaPtr -> - {# call unsafe widget_intersect #} +widgetAddAccelerator :: WidgetClass self => self + -> String -- ^ @accelSignal@ - widget signal to emit on accelerator + -- activation + -> AccelGroup -- ^ @accelGroup@ - accel group for this widget, added to + -- its toplevel + -> KeyVal -- ^ @accelKey@ - the key of the accelerator + -> [Modifier] -- ^ @accelMods@ - modifier key combination of the + -- accelerator + -> [AccelFlags] -- ^ @accelFlags@ - flag accelerators, e.g. 'AccelVisible' + -> IO () +widgetAddAccelerator self accelSignal accelGroup accelKey accelMods accelFlags = + withUTFString accelSignal $ \accelSignalPtr -> + {# call gtk_widget_add_accelerator #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 491 - (castPtr areaPtr) - (castPtr nullPtr) + accelSignalPtr + accelGroup + (fromIntegral accelKey) + ((fromIntegral . fromFlags) accelMods) + ((fromIntegral . fromFlags) accelFlags) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 497 --- | Computes the intersection of a widget's area and @area@, returning the --- intersection, and returns @Nothing@ if there was no intersection. +-- %hash c:3442 d:dfe8 +-- | Removes an accelerator from @widget@, previously installed with +-- 'widgetAddAccelerator'. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 501 -widgetIntersect :: WidgetClass self => self - -> Rectangle -- ^ @area@ - a rectangle - -> IO (Maybe Rectangle) -- ^ returns the intersection or @Nothing@ -widgetIntersect self area = - with area $ \areaPtr -> - alloca $ \intersectionPtr -> do - hasIntersection <- {# call unsafe widget_intersect #} +widgetRemoveAccelerator :: WidgetClass self => self + -> AccelGroup -- ^ @accelGroup@ - accel group for this widget + -> KeyVal -- ^ @accelKey@ - the key of the accelerator + -> [Modifier] -- ^ @accelMods@ - modifier key combination of the + -- accelerator + -> IO Bool -- ^ returns whether an accelerator was installed and could + -- be removed +widgetRemoveAccelerator self accelGroup accelKey accelMods = + liftM toBool $ + {# call gtk_widget_remove_accelerator #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 512 - (castPtr areaPtr) - (castPtr intersectionPtr) - if (toBool hasIntersection) - then liftM Just $ peek intersectionPtr - else return Nothing + accelGroup + (fromIntegral accelKey) + ((fromIntegral . fromFlags) accelMods) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 516 --- | Computes the intersection of a widget's area and @region@, returning --- the intersection. The result may be empty, use --- 'Graphics.UI.Gtk.Gdk.Region.regionEmpty' to check. +-- %hash c:f8d4 d:bd7f +-- | Given an accelerator group, @accelGroup@, and an accelerator path, +-- @accelPath@, sets up an accelerator in @accelGroup@ so whenever the key +-- binding that is defined for @accelPath@ is pressed, @widget@ will be +-- activated. This removes any accelerators (for any accelerator group) +-- installed by previous calls to 'widgetSetAccelPath'. Associating +-- accelerators with paths allows them to be modified by the user and the +-- modifications to be saved for future use. (See 'accelMapSave'.) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 525 -widgetRegionIntersect :: WidgetClass self => self - -> Region -- ^ @region@ - a 'Region' in the same coordinate system as the - -- widget's allocation. That is, relative to the widget's - -- 'DrawWindow' for 'NoWindow' widgets; relative to the parent - -- 'DrawWindow' of the widget's 'DrawWindow' for widgets with - -- their own 'DrawWindow'. - -> IO Region -- ^ returns A region holding the intersection of the widget and - -- @region@. The coordinates of the return value are relative to - -- the widget's 'DrawWindow', if it has one, otherwise - -- it is relative to the parent's 'DrawWindow'. -widgetRegionIntersect self region = do - intersectionPtr <- {# call gtk_widget_region_intersect #} +-- This function is a low level function that would most likely be used by a +-- menu creation system like 'ItemFactory'. If you use 'ItemFactory', setting +-- up accelerator paths will be done automatically. +-- +-- Even when you you aren't using 'ItemFactory', if you only want to set up +-- accelerators on menu items 'menuItemSetAccelPath' provides a somewhat more +-- convenient interface. +-- +widgetSetAccelPath :: WidgetClass self => self + -> String -- ^ @accelPath@ - path used to look up the accelerator + -> AccelGroup -- ^ @accelGroup@ - a 'AccelGroup'. + -> IO () +widgetSetAccelPath self accelPath accelGroup = + withUTFString accelPath $ \accelPathPtr -> + {# call gtk_widget_set_accel_path #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 541 - region - makeNewRegion intersectionPtr + accelPathPtr + accelGroup hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 544 --- Manipulate widget state. +#if GTK_CHECK_VERSION(2,4,0) +-- %hash c:157e d:82ae +-- | Determines whether an accelerator that activates the signal identified by +-- @signalId@ can currently be activated. This is done by emitting the +-- 'canActivateAccel' signal on the widget the signal is attached to; if the +-- signal isn't overridden by a handler or in a derived widget, then the +-- default check is that the widget must be sensitive, and the widget and all +-- its ancestors mapped. +-- +-- * Available since Gtk+ version 2.4 +-- +widgetCanActivateAccel :: WidgetClass self => + (ConnectId self) -- ^ @signalId@ - the ID of a signal installed on @widget@ + -> IO Bool -- ^ returns @True@ if the accelerator can be activated. +widgetCanActivateAccel (ConnectId signalId self) = + liftM toBool $ + {# call gtk_widget_can_activate_accel #} + (toWidget self) + (fromIntegral signalId) +#endif hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 577 --- | Sets the sensitivity of a widget. A widget is sensitive if the user can --- interact with it. Insensitive widgets are \"grayed out\" and the user can't --- interact with them. Insensitive widgets are known as \"inactive\", --- \"disabled\", or \"ghosted\" in some other toolkits. +-- | Computes the intersection of a widget's area and @area@, returning the +-- intersection, and returns @Nothing@ if there was no intersection. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 580 -widgetSetSensitivity :: WidgetClass self => self - -> Bool -- ^ @sensitive@ - @True@ to make the widget sensitive - -> IO () -widgetSetSensitivity self sensitive = - {# call widget_set_sensitive #} +widgetIntersect :: WidgetClass self => self + -> Rectangle -- ^ @area@ - a rectangle + -> IO (Maybe Rectangle) -- ^ returns the intersection or @Nothing@ +widgetIntersect self area = + with area $ \areaPtr -> + alloca $ \intersectionPtr -> do + hasIntersection <- {# call unsafe widget_intersect #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 588 - (fromBool sensitive) + (castPtr areaPtr) + (castPtr intersectionPtr) + if (toBool hasIntersection) + then liftM Just $ peek intersectionPtr + else return Nothing hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 594 --- | Sets the minimum size of a widget; that is, the widget's size request --- will be @width@ by @height@. You can use this function to force a widget to --- be either larger or smaller than it normally would be. --- --- In most cases, 'Graphics.UI.Gtk.Windows.Window.windowSetDefaultSize' --- is a better choice for toplevel --- windows than this function; setting the default size will still allow users --- to shrink the window. Setting the size request will force them to leave the --- window at least as large as the size request. When dealing with window --- sizes, 'Graphics.UI.Gtk.Windows.Window.windowSetGeometryHints' can be a --- useful function as well. --- --- Note the inherent danger of setting any fixed size - themes, translations --- into other languages, different fonts, and user action can all change the --- appropriate size for a given widget. So, it's basically impossible to --- hardcode a size that will always be correct. --- --- The size request of a widget is the smallest size a widget can accept --- while still functioning well and drawing itself correctly. However in some --- strange cases a widget may be allocated less than its requested size, and in --- many cases a widget may be allocated more space than it requested. --- --- If the size request in a given direction is -1 (unset), then the --- \"natural\" size request of the widget will be used instead. --- --- Widgets can't actually be allocated a size less than 1 by 1, but you can --- pass 0,0 to this function to mean \"as small as possible.\" +-- | Check if the widget intersects with a given area. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 596 -widgetSetSizeRequest :: WidgetClass self => self - -> Int -- ^ @width@ - width @widget@ should request, or -1 to unset - -> Int -- ^ @height@ - height @widget@ should request, or -1 to unset - -> IO () -widgetSetSizeRequest self width height = - {# call widget_set_size_request #} +widgetHasIntersection :: WidgetClass self => self + -> Rectangle -- ^ @area@ - a rectangle + -> IO Bool -- ^ returns @True@ if there was an intersection +widgetHasIntersection self area = [_$_] + liftM toBool $ + with area $ \areaPtr -> + {# call unsafe widget_intersect #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 604 - (fromIntegral width) - (fromIntegral height) + (castPtr areaPtr) + (castPtr nullPtr) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 607 --- | Gets the size request that was explicitly set for the widget using --- 'widgetSetSizeRequest'. A value of -1 for @width@ or @height@ --- indicates that that dimension has not been set explicitly and the natural --- requisition of the widget will be used intead. See 'widgetSetSizeRequest'. --- To get the size a widget will actually use, call connect to the --- signal 'onSizeRequest' instead of calling this function. +-- %hash d:1cab +-- | Determines if the widget is the focus widget within its toplevel. (This +-- does not mean that the 'widgetHasFocus' attribute is necessarily set; +-- 'widgetHasFocus' will only be set if the toplevel widget additionally has +-- the global input focus.) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 613 -widgetGetSizeRequest :: WidgetClass self => self - -> IO (Int, Int) -- ^ @(width, height)@ -widgetGetSizeRequest self = - alloca $ \widthPtr -> - alloca $ \heightPtr -> do - {# call gtk_widget_get_size_request #} +widgetGetIsFocus :: WidgetClass self => self + -> IO Bool -- ^ returns @True@ if the widget is the focus widget. +widgetGetIsFocus self = + liftM toBool $ + {# call unsafe widget_is_focus #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 619 - widthPtr - heightPtr - width <- peek widthPtr - height <- peek heightPtr - return (fromIntegral width, fromIntegral height) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 620 --- | Causes the widget to have the keyboard focus for the 'Window' it's inside. --- The widget must be a focusable widget, such as a 'Entry'; something like --- 'Frame' won't work. (More precisely, it must have the "CanFocus" flag set.) +-- %hash d:e1e +-- | Causes @widget@ to have the keyboard focus for the 'Window' it's inside. +-- @widget@ must be a focusable widget, such as a +-- 'Graphics.UI.Gtk.Entry.Entry'; something like +-- 'Graphics.UI.Gtk.Ornaments.Frame' won't work. (More precisely, it must have +-- the 'widgetCanFocus' flag set.) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 632 --- | Sets whether the application intends to draw on the widget in response --- to an 'onExpose' signal. +-- %hash c:e5e9 d:412a +-- | Causes @widget@ to become the default widget. @widget@ must have the +-- 'canDefault' flag set. The default widget is +-- activated when the user presses Enter in a window. Default widgets must be +-- activatable, that is, 'widgetActivate' should affect them. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 638 --- * This is a hint to the widget and does not affect the behavior of the --- GTK+ core; many widgets ignore this flag entirely. For widgets that do --- pay attention to the flag, such as 'EventBox' and 'Window', the effect --- is to suppress default themed drawing of the widget's background. --- (Children of the widget will still be drawn.) The application is then --- entirely responsible for drawing the widget background. --- -widgetSetAppPaintable :: WidgetClass self => self - -> Bool -- ^ @appPaintable@ - @True@ if the application will paint on the - -- widget - -> IO () -widgetSetAppPaintable self appPaintable = - {# call widget_set_app_paintable #} +widgetGrabDefault :: WidgetClass self => self -> IO () +widgetGrabDefault self = + {# call gtk_widget_grab_default #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 642 - (fromBool appPaintable) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 643 +-- %hash c:4f62 d:d05a hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 669 +-- %hash c:25b1 d:f898 +-- | Sets the sensitivity of a widget. A widget is sensitive if the user can +-- interact with it. Insensitive widgets are \"grayed out\" and the user can't +-- interact with them. Insensitive widgets are known as \"inactive\", +-- \"disabled\", or \"ghosted\" in some other toolkits. +-- +widgetSetSensitive :: WidgetClass self => self + -> Bool -- ^ @sensitive@ - @True@ to make the widget sensitive + -> IO () +widgetSetSensitive self sensitive = + {# call gtk_widget_set_sensitive #} + (toWidget self) + (fromBool sensitive) + [_$_] +-- bad spelling backwards compatability definition +widgetSetSensitivity :: WidgetClass self => self -> Bool -> IO () +widgetSetSensitivity = widgetSetSensitive + +-- | Gets the widget's parent window. +-- +widgetGetParentWindow :: WidgetClass self => self -> IO DrawWindow +widgetGetParentWindow self = + makeNewGObject mkDrawWindow $ + {# call gtk_widget_get_parent_window #} + (toWidget self) + hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 702 --- should be called whenever a signal receiving an 'Event' is disconected. [_$_] +-- should be called whenever all signals receiving an 'Event' +-- have been disconected. [_$_] hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 720 - {# call widget_add_events #} + {# call unsafe widget_add_events #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 734 --- | Sets the extension events. +-- %hash c:468a d:49a0 +-- | Sets the event mask (see 'EventMask') for a widget. The event mask +-- determines which events a widget will receive. Keep in mind that different +-- widgets have different default event masks, and by changing the event mask +-- you may disrupt a widget's functionality, so be careful. This function must +-- be called while a widget is unrealized. Consider 'widgetAddEvents' for +-- widgets that are already realized, or if you want to preserve the existing +-- event mask. This function can't be used with 'NoWindow' widgets; to get +-- events on those widgets, place them inside a +-- 'Graphics.UI.Gtk.Misc.EventBox' and receive events on the event box. +-- +widgetSetEvents :: WidgetClass self => self + -> [EventMask] -- ^ @events@ - event mask + -> IO () +widgetSetEvents self events = + {# call unsafe widget_set_events #} + (toWidget self) + (fromIntegral $ fromFlags events) + +-- %hash c:4f2c d:781 +-- | Sets the extension events mask to @mode@. See 'ExtensionMode' and +-- 'inputSetExtensionEvents'. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 765 +-- %hash c:c824 d:e611 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 776 --- Widget browsing. - +-- %hash c:270b d:8877 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 790 --- | Determines whether @widget@ is somewhere inside @ancestor@, possibly with --- intermediate containers. +-- %hash c:17bc d:f8f9 +-- | Gets the first ancestor of @widget@ with type @widgetType@. For example, +-- @widgetGetAncestor widget gTypeBox@ gets the first 'Box' that's +-- an ancestor of @widget@. See note about checking for a toplevel +-- 'Window' in the docs for 'widgetGetToplevel'. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 796 -widgetIsAncestor :: (WidgetClass self, WidgetClass ancestor) => - self -- ^ @widget@ - the widget in question - -> ancestor -- ^ @ancestor@ - another 'Widget' - -> IO Bool -- ^ returns @True@ if @ancestor@ contains @widget@ as a child, - -- grandchild, great grandchild, etc. -widgetIsAncestor self ancestor = - liftM toBool $ - {# call unsafe widget_is_ancestor #} - (toWidget self) - (toWidget ancestor) - --- | Moves a widget from one 'Container' to another. +-- Note that unlike 'widgetIsAncestor', 'widgetGetAncestor' considers +-- @widget@ to be an ancestor of itself. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 799 -widgetReparent :: (WidgetClass self, WidgetClass newParent) => self - -> newParent -- ^ @newParent@ - a 'Container' to move the widget into - -> IO () -widgetReparent self newParent = - {# call widget_reparent #} +widgetGetAncestor :: WidgetClass self => self + -> GType -- ^ @widgetType@ - ancestor type + -> IO (Maybe Widget) -- ^ returns the ancestor widget, or @Nothing@ if not found +widgetGetAncestor self widgetType = do + ptr <- {# call gtk_widget_get_ancestor #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 805 - (toWidget newParent) + widgetType + if ptr==nullPtr then return Nothing else + liftM Just $ makeNewObject mkWidget (return ptr) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 809 --- | Sets the reading direction on a particular widget. This direction --- controls the primary direction for widgets containing text, and also the --- direction in which the children of a container are packed. The ability to --- set the direction is present in order so that correct localization into --- languages with right-to-left reading directions can be done. Generally, --- applications will let the default reading direction present, except for --- containers where the containers are arranged in an order that is explicitely --- visual rather than logical (such as buttons for text justification). --- --- If the direction is set to 'TextDirNone', then the value set by --- 'widgetSetDefaultDirection' will be used. --- -widgetSetDirection :: WidgetClass self => self -> TextDirection -> IO () -widgetSetDirection self dir = - {# call widget_set_direction #} - (toWidget self) - ((fromIntegral . fromEnum) dir) - --- | Gets the reading direction for a particular widget. See --- 'widgetSetDirection'. --- -widgetGetDirection :: WidgetClass self => self -> IO TextDirection -widgetGetDirection self = - liftM (toEnum . fromIntegral) $ - {# call widget_get_direction #} - (toWidget self) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 810 --- | Invalidates the rectangular area of @widget@ defined by @x@, @y@, @width@ --- and @height@ by calling --- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowInvalidateRect' on the widget's --- 'Graphics.UI.Gtk.Gdk.DrawWindow.DrawWindow' and --- all its child windows. Once the main loop becomes idle (after the current --- batch of events has been processed, roughly), the window will receive expose --- events for the union of all regions that have been invalidated. +-- %hash c:bd95 d:eb94 +-- | Gets the colormap that will be used to render @widget@. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 813 --- Normally you would only use this function in widget implementations. You --- might also use it, or 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowInvalidateRect' --- directly, to schedule a redraw --- of a 'Graphics.UI.Gtk.Gdk.DrawWindow.DrawingArea' or some portion thereof. --- --- Frequently you can just call --- 'Graphics.UI.Gtk.Gdk.DrawWindow.windowInvalidateRect' or --- 'Graphics.UI.Gtk.Gdk.DrawWindow.windowInvalidateRegion' instead of this --- function. Those functions will --- invalidate only a single window, instead of the widget and all its children. --- --- The advantage of adding to the invalidated region compared to simply --- drawing immediately is efficiency; using an invalid region ensures that you --- only have to redraw one time. --- -widgetQueueDrawArea :: WidgetClass self => self - -> Int -- ^ @x@ - x coordinate of upper-left corner of rectangle to redraw - -> Int -- ^ @y@ - y coordinate of upper-left corner of rectangle to redraw - -> Int -- ^ @width@ - width of region to draw - -> Int -- ^ @height@ - height of region to draw - -> IO () -widgetQueueDrawArea self x y width height = - {# call gtk_widget_queue_draw_area #} - (toWidget self) - (fromIntegral x) - (fromIntegral y) - (fromIntegral width) - (fromIntegral height) - --- | Widgets are double buffered by default; you can use this function to turn --- off the buffering. \"Double buffered\" simply means that --- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowBeginPaintRegion' and --- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowEndPaint' are called automatically --- around expose events sent to the widget. --- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowBeginPaintRegion' diverts all --- drawing to a widget's window to an offscreen buffer, and --- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowEndPaint' --- draws the buffer to the screen. The result is that users see the window --- update in one smooth step, and don't see individual graphics primitives --- being rendered. --- --- In very simple terms, double buffered widgets don't flicker, so you would --- only use this function to turn off double buffering if you had special needs --- and really knew what you were doing. --- --- Note: if you turn off double-buffering, you have to handle expose events, --- since even the clearing to the background color or pixmap will not happen --- automatically (as it is done in --- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowBeginPaint'). --- -widgetSetDoubleBuffered :: WidgetClass self => self - -> Bool -- ^ @doubleBuffered@ - @True@ to double-buffer a widget - -> IO () -widgetSetDoubleBuffered self doubleBuffered = - {# call gtk_widget_set_double_buffered #} +widgetGetColormap :: WidgetClass self => self + -> IO Colormap -- ^ returns the colormap used by @widget@ +widgetGetColormap self = + makeNewGObject mkColormap $ + {# call gtk_widget_get_colormap #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 819 - (fromBool doubleBuffered) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 820 --- | Sets whether the entire widget is queued for drawing when its size --- allocation changes. By default, this setting is @True@ and the entire widget --- is redrawn on every size change. If your widget leaves the upper left --- unchanged when made bigger, turning this setting on will improve --- performance. --- --- Note that for \"no window\" widgets setting this flag to @False@ turns off --- all allocation on resizing: the widget will not even redraw if its position --- changes; this is to allow containers that don't draw anything to avoid --- excess invalidations. If you set this flag on a \"no window\" widget that --- /does/ draw its window, you are responsible for invalidating both --- the old and new allocation of the widget when the widget is moved and --- responsible for invalidating regions newly when the widget increases size. +-- %hash c:cba1 d:ffeb +-- | Sets the colormap for the widget to the given value. Widget must not have +-- been previously realized. This probably should only be used from an 'init' +-- function (i.e. from the constructor for the widget). hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 825 -widgetSetRedrawOnAllocate :: WidgetClass self => self - -> Bool -- ^ @redrawOnAllocate@ - if @True@, the entire widget will be - -- redrawn when it is allocated to a new size. Otherwise, only the - -- new portion of the widget will be redrawn. +widgetSetColormap :: WidgetClass self => self + -> Colormap -- ^ @colormap@ - a colormap hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 828 -widgetSetRedrawOnAllocate self redrawOnAllocate = - {# call gtk_widget_set_redraw_on_allocate #} - (toWidget self) - (fromBool redrawOnAllocate) - --- | Gets the widget's parent window. --- -widgetGetParentWindow :: WidgetClass self => self -> IO DrawWindow -widgetGetParentWindow self = - makeNewGObject mkDrawWindow $ - {# call gtk_widget_get_parent_window #} +widgetSetColormap self colormap = + {# call gtk_widget_set_colormap #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 831 + colormap hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 833 +-- %hash c:3522 d:5637 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 854 +-- %hash c:499d +-- | Determines whether @widget@ is somewhere inside @ancestor@, possibly with +-- intermediate containers. +-- +widgetIsAncestor :: (WidgetClass self, WidgetClass ancestor) => + self -- ^ @widget@ - the widget in question + -> ancestor -- ^ @ancestor@ - another 'Widget' + -> IO Bool -- ^ returns @True@ if @ancestor@ contains @widget@ as a child, + -- grandchild, great grandchild, etc. +widgetIsAncestor self ancestor = + liftM toBool $ + {# call unsafe widget_is_ancestor #} + (toWidget self) + (toWidget ancestor) + +-- %hash c:8661 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 899 --- | Obtains the full path to the widget. The path is simply the name of a +-- %hash c:596c d:b7e5 +-- | Sets the 'Style' for a widget. You probably don't want +-- to use this function; it interacts badly with themes, because themes work by +-- replacing the 'Style'. Instead, use 'widgetModifyStyle'. +-- +widgetSetStyle :: WidgetClass self => self + -> Maybe Style -- ^ @style@ - a 'Style', or @Nothing@ to remove the effect of a previous + -- 'widgetSetStyle' and go back to the default style + -> IO () +widgetSetStyle self style = + {# call gtk_widget_set_style #} + (toWidget self) + (fromMaybe (mkStyle nullForeignPtr) style) + +-- | Retrieve the 'Style' associated with the widget. +-- +widgetGetStyle :: WidgetClass widget => widget -> IO Style +widgetGetStyle widget = do + {# call gtk_widget_ensure_style #} (toWidget widget) + makeNewGObject mkStyle $ {# call gtk_widget_get_style #} (toWidget widget) + +-- %hash c:d5ed d:dc10 +-- | Pushes @cmap@ onto a global stack of colormaps; the topmost colormap on +-- the stack will be used to create all widgets. Remove @cmap@ with +-- 'widgetPopColormap'. There's little reason to use this function. +-- +widgetPushColormap :: + Colormap -- ^ @cmap@ - a 'Colormap' + -> IO () +widgetPushColormap cmap = + {# call gtk_widget_push_colormap #} + cmap + +-- %hash c:7300 d:2920 +-- | Removes a colormap pushed with 'widgetPushColormap'. +-- +widgetPopColormap :: IO () +widgetPopColormap = + {# call gtk_widget_pop_colormap #} + +-- %hash c:1f73 d:590e +-- | Sets the default colormap to use when creating widgets. +-- 'widgetPushColormap' is a better function to use if you only want to affect +-- a few widgets, rather than all widgets. +-- +widgetSetDefaultColormap :: + Colormap -- ^ @colormap@ - a 'Colormap' + -> IO () +widgetSetDefaultColormap colormap = + {# call gtk_widget_set_default_colormap #} + colormap + +-- %hash c:e71b d:72c2 +-- | Returns the default style used by all widgets initially. +-- +widgetGetDefaultStyle :: + IO Style -- ^ returns the default style. This 'Style' object is owned by + -- Gtk and should not be modified. +widgetGetDefaultStyle = + makeNewGObject mkStyle $ + {# call gtk_widget_get_default_style #} + +-- %hash c:d731 d:52bf +-- | Obtains the default colormap used to create widgets. +-- +widgetGetDefaultColormap :: + IO Colormap -- ^ returns default widget colormap +widgetGetDefaultColormap = + makeNewGObject mkColormap $ + {# call gtk_widget_get_default_colormap #} + +-- | Sets the reading direction on a particular widget. This direction +-- controls the primary direction for widgets containing text, and also the +-- direction in which the children of a container are packed. The ability to +-- set the direction is present in order so that correct localization into +-- languages with right-to-left reading directions can be done. Generally, +-- applications will let the default reading direction present, except for +-- containers where the containers are arranged in an order that is explicitely +-- visual rather than logical (such as buttons for text justification). +-- +-- If the direction is set to 'TextDirNone', then the value set by +-- 'widgetSetDefaultDirection' will be used. +-- +widgetSetDirection :: WidgetClass self => self -> TextDirection -> IO () +widgetSetDirection self dir = + {# call widget_set_direction #} + (toWidget self) + ((fromIntegral . fromEnum) dir) + +-- | Gets the reading direction for a particular widget. See +-- 'widgetSetDirection'. +-- +widgetGetDirection :: WidgetClass self => self -> IO TextDirection +widgetGetDirection self = + liftM (toEnum . fromIntegral) $ + {# call widget_get_direction #} + (toWidget self) + +-- %hash c:ff9a +-- | Sets the default reading direction for widgets where the direction has +-- not been explicitly set by 'widgetSetDirection'. +-- +widgetSetDefaultDirection :: [_$_] + TextDirection -- ^ @dir@ - the new default direction. This cannot be + -- 'TextDirNone'. + -> IO () +widgetSetDefaultDirection dir = + {# call gtk_widget_set_default_direction #} + ((fromIntegral . fromEnum) dir) + +-- | Obtains the current default reading direction. See +-- 'widgetSetDefaultDirection'. +-- +widgetGetDefaultDirection :: IO TextDirection +widgetGetDefaultDirection = + liftM (toEnum . fromIntegral) $ + {# call gtk_widget_get_default_direction #} + +-- %hash c:c7ba d:3a9c +-- | Sets a shape for this widget's 'DrawWindow'. This allows for transparent +-- windows etc., see 'windowShapeCombineMask' for more information. +-- +widgetShapeCombineMask :: WidgetClass self => self + -> Maybe Bitmap -- ^ @shapeMask@ - shape to be added, or @Nothint@ to remove an + -- existing shape. + -> Int -- ^ @offsetX@ - X position of shape mask with respect to @window@. + -> Int -- ^ @offsetY@ - Y position of shape mask with respect to @window@. + -> IO () +widgetShapeCombineMask self shapeMask offsetX offsetY = + case (fromMaybe (mkPixmap nullForeignPtr) shapeMask) of + Pixmap fPtr -> withForeignPtr fPtr $ \bitmapPtr -> + {# call gtk_widget_shape_combine_mask #} + (toWidget self) + (castPtr bitmapPtr) + (fromIntegral offsetX) + (fromIntegral offsetY) + +#if GTK_CHECK_VERSION(2,10,0) +-- %hash c:3c29 d:68e2 +-- | Sets an input shape for this widget's GDK window. This allows for windows +-- which react to mouse click in a nonrectangular region, see +-- 'windowInputShapeCombineMask' for more information. +-- +-- * Available since Gtk+ version 2.10 +-- +widgetInputShapeCombineMask :: WidgetClass self => self + -> Maybe Bitmap -- ^ @shapeMask@ - shape to be added, or @Nothint@ to remove an + -- existing shape. + -> Int -- ^ @offsetX@ - X position of shape mask with respect to @window@. + -> Int -- ^ @offsetY@ - Y position of shape mask with respect to @window@. + -> IO () +widgetInputShapeCombineMask self shapeMask offsetX offsetY = + case (fromMaybe (mkPixmap nullForeignPtr) shapeMask) of + Pixmap fPtr -> withForeignPtr fPtr $ \bitmapPtr -> + {# call gtk_widget_input_shape_combine_mask #} + (toWidget self) + (castPtr bitmapPtr) + (fromIntegral offsetX) + (fromIntegral offsetY) +#endif + +-- %hash c:7e36 d:616f +-- | Obtains the full path to @widget@. The path is simply the name of a hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1091 +-- %hash c:d4a6 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1114 +-- %hash c:769e hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1125 --- | Sets a widgets composite name. A child widget of a container is --- composite if it serves as an internal widget and, thus, is not --- added by the user. --- -widgetSetCompositeName :: WidgetClass self => self - -> String -- ^ @name@ - the name to set. - -> IO () -widgetSetCompositeName self name = - withUTFString name $ \namePtr -> - {# call gtk_widget_set_composite_name #} - (toWidget self) - namePtr - --- | Returns the parent container of @widget@. --- --- * Returns the parent container of @widget@ if it has one. --- -widgetGetParent :: WidgetClass self => self - -> IO (Maybe Widget) [_$_] -widgetGetParent self = do - parentPtr <- {# call gtk_widget_get_parent #} (toWidget self) - if parentPtr==nullPtr then return Nothing else - liftM Just $ makeNewObject mkWidget (return parentPtr) - --- | Sets the default reading direction for widgets where the direction has --- not been explicitly set by 'widgetSetDirection'. --- -widgetSetDefaultDirection :: [_$_] - TextDirection -- ^ @dir@ - the new default direction. This cannot be - -- 'TextDirNone'. - -> IO () -widgetSetDefaultDirection dir = - {# call gtk_widget_set_default_direction #} - ((fromIntegral . fromEnum) dir) - --- | Obtains the current default reading direction. See --- 'widgetSetDefaultDirection'. --- -widgetGetDefaultDirection :: IO TextDirection -widgetGetDefaultDirection = - liftM (toEnum . fromIntegral) $ - {# call gtk_widget_get_default_direction #} - --- | Retrieve the 'Style' associated with the widget. --- -widgetGetStyle :: WidgetClass widget => widget -> IO Style -widgetGetStyle widget = do - {# call gtk_widget_ensure_style #} (toWidget widget) - makeNewGObject mkStyle $ {# call gtk_widget_get_style #} (toWidget widget) - hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1168 +-- %hash c:5550 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1185 +-- %hash c:2c5 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1209 +-- %hash c:d2ba hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1228 +-- %hash c:ac08 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1254 +-- %hash c:38d7 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1299 +-- | Prepare text for display. +-- +-- The 'PangoLayout' represents the rendered text. It can be shown on screen +-- by calling 'Graphics.UI.Gtk.Gdk.Drawable.drawLayout'. +-- +-- The returned 'PangoLayout' shares the same font information ('PangoContext') as this +-- widget. If this information changes, the 'PangoLayout' should change. The +-- following code ensures that the displayed text always reflects the widget's +-- settings: +-- +-- > l <- widgetCreateLayout w "My Text." +-- > let update = do +-- > layoutContextChanged l +-- > -- update the Drawables which show this layout +-- > w `onDirectionChanged` update +-- > w `onStyleChanged` update +-- +widgetCreateLayout :: WidgetClass self => self + -> String -- ^ @text@ - text to set on the layout + -> IO PangoLayout +widgetCreateLayout self text = do + pl <- constructNewGObject mkPangoLayoutRaw $ + withUTFString text $ \textPtr -> + {# call unsafe widget_create_pango_layout #} + (toWidget self) + textPtr + ps <- makeNewPangoString text + psRef <- newIORef ps + return (PangoLayout psRef pl) + +-- %hash c:cee d:1d29 hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1345 - -> StockId -- ^ the stock ID of the icon - -> IconSize -- ^ @size@ - a stock size. The size - -- 'Graphics.UI.Gtk.General.IconFactory.IconSizeInvalid' means - -- render at the size of the source and don't scale (if there are - -- multiple source sizes, Gtk+ picks one of the available sizes). - -> String -- ^ @detail@ - render detail to pass to theme engine - -> IO (Maybe Pixbuf) -- ^ the new 'Graphics.UI.Gtk.Gdk.Pixbuf.Pixbuf' - -- if the stock icon was found -widgetRenderIcon self stockId size detail = do - pixbufPtr <- - withUTFString detail $ \detailPtr -> - withUTFString stockId $ \stockIdPtr -> - {# call gtk_widget_render_icon #} - (toWidget self) stockIdPtr ((fromIntegral . fromEnum) size) detailPtr - if pixbufPtr==nullPtr then return Nothing else [_$_] - liftM Just $ constructNewGObject mkPixbuf (return pixbufPtr) + -> String -- ^ @stockId@ - a stock ID + -> IconSize -- ^ @size@ - a stock size + -> String -- ^ @detail@ - render detail to pass to theme engine + -> IO (Maybe Pixbuf) -- ^ returns a new pixbuf, or @Nothing@ if the stock ID + -- wasn't known +widgetRenderIcon self stockId size detail = + maybeNull (makeNewGObject mkPixbuf) $ + withUTFString detail $ \detailPtr -> + withUTFString stockId $ \stockIdPtr -> + {# call gtk_widget_render_icon #} + (toWidget self) + stockIdPtr + ((fromIntegral . fromEnum) size) + detailPtr hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1360 --- | Set if this widget can receive keyboard input. +-- %hash c:62f d:1863 +-- | Invalidates the rectangular area of @widget@ defined by @x@, @y@, @width@ +-- and @height@ by calling +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowInvalidateRect' on the widget's +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.DrawWindow' and all its child windows. Once +-- the main loop becomes idle (after the current batch of events has been +-- processed, roughly), the window will receive expose events for the union of +-- all regions that have been invalidated. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1369 --- * To use the 'onKeyPress' event, the widget must be allowed --- to get the input focus. Once it has the input focus all keyboard --- input is directed to this widget. +-- Normally you would only use this function in widget implementations. In +-- particular, you might use it, or +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowInvalidateRect' directly, to +-- schedule a redraw of a 'Graphics.UI.Gtk.Gdk.DrawWindow.DrawingArea' or some +-- portion thereof. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1375 -widgetSetCanFocus :: WidgetClass self => self -> Bool -> IO () -widgetSetCanFocus = objectSetPropertyBool "can_focus" +-- Frequently you can just call +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.windowInvalidateRect' or +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.windowInvalidateRegion' instead of this +-- function. Those functions will invalidate only a single window, instead of +-- the widget and all its children. +-- +-- The advantage of adding to the invalidated region compared to simply +-- drawing immediately is efficiency; using an invalid region ensures that you +-- only have to redraw one time. +-- +widgetQueueDrawArea :: WidgetClass self => self + -> Int -- ^ @x@ - x coordinate of upper-left corner of rectangle to redraw + -> Int -- ^ @y@ - y coordinate of upper-left corner of rectangle to redraw + -> Int -- ^ @width@ - width of region to draw + -> Int -- ^ @height@ - height of region to draw + -> IO () +widgetQueueDrawArea self x y width height = + {# call gtk_widget_queue_draw_area #} + (toWidget self) + (fromIntegral x) + (fromIntegral y) + (fromIntegral width) + (fromIntegral height) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1399 --- | Check if this widget can receive keyboard input. +-- %hash c:5ffb d:3e1a +-- | Recursively resets the shape on this widget and its descendants. hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1402 -widgetGetCanFocus :: WidgetClass self => self -> IO Bool -widgetGetCanFocus = objectGetPropertyBool "can_focus" +widgetResetShapes :: WidgetClass self => self -> IO () +widgetResetShapes self = + {# call gtk_widget_reset_shapes #} + (toWidget self) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1407 -widgetGetColormap :: WidgetClass self => self - -> IO Colormap -- ^ returns the colormap used by @widget@ -widgetGetColormap self = - makeNewGObject mkColormap $ - {# call gtk_widget_get_colormap #} +-- | Sets whether the application intends to draw on the widget in response +-- to an 'onExpose' signal. +-- +-- * This is a hint to the widget and does not affect the behavior of the +-- GTK+ core; many widgets ignore this flag entirely. For widgets that do +-- pay attention to the flag, such as 'EventBox' and 'Window', the effect +-- is to suppress default themed drawing of the widget's background. +-- (Children of the widget will still be drawn.) The application is then +-- entirely responsible for drawing the widget background. +-- +widgetSetAppPaintable :: WidgetClass self => self + -> Bool -- ^ @appPaintable@ - @True@ if the application will paint on the + -- widget + -> IO () +widgetSetAppPaintable self appPaintable = + {# call widget_set_app_paintable #} hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1424 + (fromBool appPaintable) hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1426 -widgetSetColormap :: WidgetClass self => self - -> Colormap -- ^ @colormap@ - a colormap +-- %hash c:89b2 d:e14d +-- | Widgets are double buffered by default; you can use this function to turn +-- off the buffering. \"Double buffered\" simply means that +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowBeginPaintRegion' and +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowEndPaint' are called automatically +-- around expose events sent to the widget. +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowBeginPaintRegion' diverts all +-- drawing to a widget's window to an offscreen buffer, and +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowEndPaint' +-- draws the buffer to the screen. The result is that users see the window +-- update in one smooth step, and don't see individual graphics primitives +-- being rendered. +-- +-- In very simple terms, double buffered widgets don't flicker, so you would +-- only use this function to turn off double buffering if you had special needs +-- and really knew what you were doing. +-- +-- Note: if you turn off double-buffering, you have to handle expose events, +-- since even the clearing to the background color or pixmap will not happen +-- automatically (as it is done in +-- 'Graphics.UI.Gtk.Gdk.DrawWindow.drawWindowBeginPaint'). +-- +widgetSetDoubleBuffered :: WidgetClass self => self + -> Bool -- ^ @doubleBuffered@ - @True@ to double-buffer a widget hunk ./gtk/Graphics/UI/Gtk/Abstract/Widget.chs.pp 1451 -widgetSetColormap self colormap = - {# call gtk_widget_set_colormap #} +widgetSetDoubleBuffered self doubleBuffered = + {# call gtk_widget_set_double_buffered #} + (toWidget self) + (fromBool doubleBuffered) + +-- %hash c:d61 d:ac24 +-- | Sets whether the entire widget is queued for drawing when its size +-- allocation changes. By default, this setting is @True@ and the entire widget +-- is redrawn on every size change. If your widget leaves the upper left +-- unchanged when made bigger, turning this setting on will improve +-- performance. +-- +-- Note that for \"no window\" widgets setting this flag to @False@ turns off +-- all allocation on resizing: the widget will not even redraw if its position +-- changes; this is to allow containers that don't draw anything to avoid +-- excess invalidations. If you set this flag on a \"no window\" widget that +-- /does/ draw its window, you are responsible for invalidating both +-- the old and new allocation of the widget when the widget is moved and +-- responsible for invalidating regions newly when the widget increases size. +-- +widgetSetRedrawOnAllocate :: WidgetClass self => self + -> Bool -- ^ @redrawOnAllocate@ - if @True@, the entire widget will be + -- redrawn when it is allocated to a new size. Otherwise, only the + -- new portion of the widget will be redrawn. + -> IO () +widgetSetRedrawOnAllocate self redrawOnAllocate = + {# call gtk_widget_set_redraw_on_allocate #} + (toWidget self) + (fromBool redrawOnAllocate) + +-- | Sets a widgets composite name. A child widget of a container is +-- composite if it serves as an internal widget and, thus, is not +-- added by the user. +-- +widgetSetCompositeName :: WidgetClass self => self + -> String -- ^ @name@ - the name to set. + -> IO () +widgetSetCompositeName self name = + withUTFString name $ \namePtr -> + {# call gtk_widget_set_composite_name #} + (toWidget self) + namePtr + +-- %hash c:5c58 d:6895 +-- | For widgets that support scrolling, sets the scroll adjustments and +-- returns @True@. For widgets that don't support scrolling, does nothing and +-- returns @False@. Widgets that don't support scrolling can be scrolled by +-- placing them in a 'Viewport', which does support scrolling. +-- +widgetSetScrollAdjustments :: WidgetClass self => self + -> Maybe Adjustment -- ^ @hadjustment@ - an adjustment for horizontal scrolling, or + -- @Nothing@ + -> Maybe Adjustment -- ^ @vadjustment@ - an adjustment for vertical scrolling, or + -- @Nothing@ + -> IO Bool -- ^ returns @True@ if the widget supports scrolling +widgetSetScrollAdjustments self hadjustment vadjustment = + liftM toBool $ + {# call gtk_widget_set_scroll_adjustments #} + (toWidget self) + (fromMaybe (mkAdjustment nullForeignPtr) hadjustment) + (fromMaybe (mkAdjustment nullForeignPtr) vadjustment) + +-- | Computes the intersection of a widget's area and @region@, returning +-- the intersection. The result may be empty, use +-- 'Graphics.UI.Gtk.Gdk.Region.regionEmpty' to check. +-- +widgetRegionIntersect :: WidgetClass self => self + -> Region -- ^ @region@ - a 'Region' in the same coordin... [truncated message content] |