sifflet-lib-1.2.5: Library of modules shared by sifflet and its tests and its exporters.

Safe HaskellSafe-Infered

Sifflet.UI.LittleGtk

Description

The purpose of this module is simply to re-export the Gtk functions and types that I use, and avoid those that I don't, particularly those that conflict with names in Sifflet, like Layout. Just hiding these is not enough, because Graphics.UI.Gtk keeps changing what it exports. For example, in 0.10.5 it no longer exports Function, fill, function.

Synopsis

Documentation

data AttrOp o where

A set or update operation on an attribute.

Constructors

:= :: ReadWriteAttr o a b -> b -> AttrOp o

Assign a value to an attribute.

:~ :: ReadWriteAttr o a b -> (a -> b) -> AttrOp o

Apply an update function to an attribute.

:=> :: ReadWriteAttr o a b -> IO b -> AttrOp o

Assign the result of an IO action to an attribute.

:~> :: ReadWriteAttr o a b -> (a -> IO b) -> AttrOp o

Apply a IO update function to an attribute.

::= :: ReadWriteAttr o a b -> (o -> b) -> AttrOp o

Assign a value to an attribute with the object as an argument.

::~ :: ReadWriteAttr o a b -> (o -> a -> b) -> AttrOp o

Apply an update function to an attribute with the object as an argument.

get :: o -> ReadWriteAttr o a b -> IO a

Get an Attr of an object.

set :: o -> [AttrOp o] -> IO ()

Set a number of properties for some object.

adjustmentNew

Arguments

:: Double

value - the initial value.

-> Double

lower - the minimum value.

-> Double

upper - the maximum value.

-> Double

stepIncrement - the step increment.

-> Double

pageIncrement - the page increment.

-> Double

pageSize - the page size.

-> IO Adjustment 

Creates a new Adjustment.

The creation function take every value that is contained in the object: value is the initial value and should be between the upper and lower bounds of the slider. Clicking on the arrows increases this value by stepIncrement. Clicking in the slider advances by pageIncrement. The pageSize is needed to determine if the end of the slider is still in the range.

boxPackEnd

Arguments

:: (BoxClass self, WidgetClass child) 
=> self 
-> child

child - the Widget to be added to the box.

-> Packing 
-> Int

padding - extra space in pixels to put between this child and its neighbors, over and above the global amount specified by spacing boxSetSpacing. If child is a widget at one of the reference ends of box, then padding pixels are also put between child and the reference edge of box.

-> IO () 

Adds the child widget to the box, packed with reference to the end of the box. The child is packed after (away from end of) any other child packed with reference to the end of the box.

Note that for boxPackEnd the PackNatural option will move a child to the right in an HBox or to the bottom in an VBox if there is more space availble.

boxPackStart

Arguments

:: (BoxClass self, WidgetClass child) 
=> self 
-> child

child - the Widget to be added to the box.

-> Packing 
-> Int

padding - extra space in pixels to put between this child and its neighbors, over and above the global amount specified by spacing boxSetSpacing. If child is a widget at one of the reference ends of box, then padding pixels are also put between child and the reference edge of box.

-> IO () 

Adds the child widget to the box, packed with reference to the start of the box. The child is packed after any other child packed with reference to the start of the box.

boxPackStartDefaults

Arguments

:: (BoxClass self, WidgetClass widget) 
=> self 
-> widget

widget - the Widget to be added to the box.

-> IO () 

Like boxPackStart but uses the default parameters PackRepel and 0 for padding.

buttonNewWithLabel

Arguments

:: String

label - The text you want the Label to hold.

-> IO Button 

Creates a Button widget with a Label child containing the given text.

buttonPressEvent :: WidgetClass self => Signal self (EventM EButton Bool)

A mouse button has been depressed while the mouse pointer was within the widget area. Sets the widget's ButtonPressMask flag.

data ButtonsType

Specify what buttons this dialog should show.

  • Prebuilt sets of buttons for the dialog. If none of these choices are appropriate, simply use ButtonsNone then call dialogAddButtons.

class WidgetClass o => ContainerClass o

Instances

ContainerClass Item 
ContainerClass ListItem 
ContainerClass InputDialog 
ContainerClass CList 
ContainerClass CTree 
ContainerClass List 
ContainerClass Container 
ContainerClass ToolPalette 
ContainerClass ToolItemGroup 
ContainerClass Bin 
ContainerClass Alignment 
ContainerClass Frame 
ContainerClass AspectFrame 
ContainerClass Button 
ContainerClass ScaleButton 
ContainerClass VolumeButton 
ContainerClass LinkButton 
ContainerClass ToggleButton 
ContainerClass CheckButton 
ContainerClass RadioButton 
ContainerClass ColorButton 
ContainerClass FontButton 
ContainerClass OptionMenu 
ContainerClass MenuItem 
ContainerClass CheckMenuItem 
ContainerClass RadioMenuItem 
ContainerClass TearoffMenuItem 
ContainerClass ImageMenuItem 
ContainerClass SeparatorMenuItem 
ContainerClass Window 
ContainerClass Assistant 
ContainerClass OffscreenWindow 
ContainerClass Dialog 
ContainerClass AboutDialog 
ContainerClass ColorSelectionDialog 
ContainerClass FileSelection 
ContainerClass FileChooserDialog 
ContainerClass FontSelectionDialog 
ContainerClass MessageDialog 
ContainerClass Plug 
ContainerClass EventBox 
ContainerClass HandleBox 
ContainerClass ScrolledWindow 
ContainerClass Viewport 
ContainerClass Expander 
ContainerClass ComboBox 
ContainerClass ComboBoxEntry 
ContainerClass ToolItem 
ContainerClass ToolButton 
ContainerClass MenuToolButton 
ContainerClass ToggleToolButton 
ContainerClass RadioToolButton 
ContainerClass SeparatorToolItem 
ContainerClass Box 
ContainerClass ButtonBox 
ContainerClass HButtonBox 
ContainerClass VButtonBox 
ContainerClass VBox 
ContainerClass RecentChooserWidget 
ContainerClass ColorSelection 
ContainerClass FontSelection 
ContainerClass FileChooserWidget 
ContainerClass HBox 
ContainerClass InfoBar 
ContainerClass Combo 
ContainerClass FileChooserButton 
ContainerClass Statusbar 
ContainerClass Fixed 
ContainerClass Paned 
ContainerClass HPaned 
ContainerClass VPaned 
ContainerClass IconView 
ContainerClass Layout 
ContainerClass MenuShell 
ContainerClass Menu 
ContainerClass RecentChooserMenu 
ContainerClass MenuBar 
ContainerClass Notebook 
ContainerClass Socket 
ContainerClass Table 
ContainerClass TextView 
ContainerClass Toolbar 
ContainerClass TreeView 

containerAdd

Arguments

:: (ContainerClass self, WidgetClass widget) 
=> self 
-> widget

widget - a widget to be placed inside container

-> IO () 

Adds widget to the container. Typically used for simple containers such as Window, Frame, or Button; for more complicated layout containers such as Box or Table, this function will pick default packing parameters that may not be correct. So consider functions such as boxPackStart and tableAttach as an alternative to containerAdd in those cases. A widget may be added to only one container at a time; you can't place the same widget inside two different containers.

containerChild :: (ContainerClass self, WidgetClass widget) => WriteAttr self widget

Can be used to add a new child to the container.

containerForeach :: ContainerClass self => self -> ContainerForeachCB -> IO ()

Maps callback over each non-internal child of container. See containerForall for details on what constitutes an "internal" child. Most applications should use containerForeach, rather than containerForall.

customStoreSetColumn

Arguments

:: TypedTreeModelClass model 
=> model row

the store in which to allocate a new column

-> ColumnId row ty

the column that should be set

-> (row -> ty)

the function that sets the property

-> IO () 

Set or update a column mapping. This function should be used before the model is installed into a widget since the number of defined columns are only checked once by widgets.

dialogNew :: IO Dialog

Creates a new dialog box. Widgets should not be packed into this Window directly, but into the "upper" and "action area", which are obtained using dialogGetUpper and dialogGetActionArea.

dialogAddButton

Arguments

:: DialogClass self 
=> self 
-> String

buttonText - text of button, or stock ID

-> ResponseId

responseId - response ID for the button

-> IO Button

returns the button widget that was added

Adds a button with the given text (or a stock button, if buttonText is a stock ID) and sets things up so that clicking the button will emit the "response" signal with the given responseId. The button is appended to the end of the dialog's action area. The button widget is returned, but usually you don't need it.

dialogGetActionArea :: DialogClass dc => dc -> IO HBox

Extract the action area of a dialog box.

  • This is useful to add some special widgets that cannot be added with dialogAddActionWidget.

dialogGetUpper :: DialogClass dc => dc -> IO VBox

Get the upper part of a dialog.

  • The upper part of a dialog window consists of a VBox. Add the required widgets into this box.

dialogRun :: DialogClass self => self -> IO ResponseId

Blocks in a recursive main loop until the dialog either emits the response signal, or is destroyed. If the dialog is destroyed during the call to dialogRun, it returns ResponseNone. Otherwise, it returns the response ID from the "response" signal emission. Before entering the recursive main loop, dialogRun calls widgetShow on the dialog for you. Note that you still need to show any children of the dialog yourself.

During dialogRun, the default behavior of "delete_event" is disabled; if the dialog receives "delete_event", it will not be destroyed as windows usually are, and dialogRun will return ResponseDeleteEvent. Also, during dialogRun the dialog will be modal. You can force dialogRun to return at any time by calling dialogResponse to emit the "response" signal. Destroying the dialog during dialogRun is a very bad idea, because your post-run code won't know whether the dialog was destroyed or not. Hence, you should not call widgetDestroy before dialogRun has returned.

After dialogRun returns, you are responsible for hiding or destroying the dialog if you wish to do so.

Note that even though the recursive main loop gives the effect of a modal dialog (it prevents the user from interacting with other windows while the dialog is run), callbacks such as timeouts, IO channel watches, DND drops, etc, will be triggered during a dialogRun call.

dialogSetDefaultResponse :: DialogClass self => self -> ResponseId -> IO ()

Sets the last widget in the dialog's action area with the given ResponseId as the default widget for the dialog. Pressing "Enter" normally activates the default widget.

  • The default response is reset once it is triggered. Hence, if you hide the dialog (rather than closing it) and re-display it later, you need to call this function again.

drawWindowInvalidateRect

Arguments

:: DrawWindowClass self 
=> self 
-> Rectangle

rect - rectangle to invalidate

-> Bool

invalidateChildren - whether to also invalidate child drawWindows

-> IO () 

A convenience wrapper around drawWindowInvalidateRegion which invalidates a rectangular region. See drawWindowInvalidateRegion for details.

entryCompletionInsertPrefix :: EntryCompletion -> IO ()

Requests a prefix insertion.

  • Available since Gtk+ version 2.6

entryCompletionModel :: TreeModelClass model => ReadWriteAttr EntryCompletion (Maybe TreeModel) (Maybe model)

The model to find matches in.

entryCompletionSetTextColumn

Arguments

:: EntryCompletion 
-> ColumnId row String

column - The column in the model of completion to get strings from.

-> IO () 

Convenience function for setting up the most used case of this code: a completion list with just strings. This function will set up completion to have a list displaying all (and just) strings in the completion list, and to get those strings from column in the model of completion.

This functions creates and adds a CellRendererText for the selected column.

entryGetText :: EntryClass self => self -> IO String

Retrieves the contents of the entry widget. See also editableGetChars.

entryGetCompletion

Arguments

:: EntryClass self 
=> self 
-> IO EntryCompletion

returns The auxiliary completion object currently in use by entry.

Returns the auxiliary completion object currently in use by the entry.

  • Available since Gtk version 2.4

entryNew :: IO Entry

Creates a new Entry widget.

entrySetCompletion :: EntryClass self => self -> EntryCompletion -> IO ()

Sets the auxiliary completion object to use with the entry. All further configuration of the completion mechanism is done on completion using the EntryCompletion API.

  • Available since Gtk version 2.4

entrySetText :: EntryClass self => self -> String -> IO ()

Sets the text in the widget to the given value, replacing the current contents.

eventBoxNew :: IO EventBox

Creates a new EventBox.

expanderNew :: String -> IO Expander

Creates a new expander using the given string as the text of the label.

expanderSetExpanded :: Expander -> Bool -> IO ()

Sets the state of the expander. Set to True, if you want the child widget to be revealed, and False if you want the child widget to be hidden.

exposeEvent :: WidgetClass self => Signal self (EventM EExpose Bool)

Instructs the widget to redraw.

  • The DrawWindow that needs to be redrawn is available via eventWindow.
  • The part that needs to be redrawn is available via eventArea and eventRegion. The options are, in order of efficiency: (a) redraw the entire window, (b) ask for the eventArea and redraw that rectangle, (c) ask for the eventRegion and redraw each of those rectangles.

Only the exposed region will be updated; see also drawWindowBeginPaintRegion.

fileChooserDialogNew

Arguments

:: Maybe String

Title of the dialog (or default)

-> Maybe Window

Transient parent of the dialog (or none)

-> FileChooserAction

Open or save mode for the dialog

-> [(String, ResponseId)]

Buttons and their response codes

-> IO FileChooserDialog 

Creates a new FileChooserDialog.

fileChooserGetFilename

Arguments

:: FileChooserClass self 
=> self 
-> IO (Maybe FilePath)

returns The currently selected filename, or Nothing if no file is selected, or the selected file can't be represented with a local filename.

Gets the filename for the currently selected file in the file selector. If multiple files are selected, one of the filenames will be returned at random.

If the file chooser is in folder mode, this function returns the selected folder.

data FileChooserAction

Describes whether a FileChooser is being used to open existing files or to save to a possibly new file.

frameNew :: IO Frame

Creates a new Frame without a label.

grabAdd :: WidgetClass wd => wd -> IO ()

add a grab widget

grabRemove :: WidgetClass w => w -> IO ()

remove a grab widget

hBoxNew

Arguments

:: Bool

homogeneous - True if all children are to be given equal space allotments.

-> Int

spacing - the number of pixels to place by default between children.

-> IO HBox 

Creates a new HBox.

keyPressEvent :: WidgetClass self => Signal self (EventM EKey Bool)

A key has been depressed. Sets the widget's KeyPressMask flag.

labelNew :: Maybe String -> IO Label

Creates a new label with the given text inside it. You can pass Nothing to get an empty label widget.

labelSetText :: LabelClass self => self -> String -> IO ()

Sets the text within the Label widget. It overwrites any text that was there before.

This will also clear any previously set mnemonic accelerators.

layoutGetDrawWindow :: Layout -> IO DrawWindow

Retrieves the Drawable part.

layoutNew

Arguments

:: Maybe Adjustment

hadjustment - horizontal scroll adjustment, or Nothing

-> Maybe Adjustment

vadjustment - vertical scroll adjustment, or Nothing

-> IO Layout 

Creates a new Layout. Unless you have a specific adjustment you'd like the layout to use for scrolling, pass Nothing for hadjustment and vadjustment.

layoutPut

Arguments

:: (LayoutClass self, WidgetClass childWidget) 
=> self 
-> childWidget

childWidget - child widget

-> Int

x - X position of child widget

-> Int

y - Y position of child widget

-> IO () 

Adds childWidget to layout, at position (x,y). layout becomes the new parent container of childWidget.

layoutSetSize

Arguments

:: LayoutClass self 
=> self 
-> Int

width - width of entire scrollable area

-> Int

height - height of entire scrollable area

-> IO () 

Sets the size of the scrollable area of the layout.

listStoreNew :: [a] -> IO (ListStore a)

Create a new TreeModel that contains a list of elements.

makeColumnIdString :: Int -> ColumnId row String

Create a ColumnId to extract an string.

menuPopup

Arguments

:: MenuClass self 
=> self

The menu to be shown.

-> Maybe (MouseButton, TimeStamp)

The mouse button returned by eventButton and the time of the event returned by eventTime. These values are used to match the corresponding release of the button. If this context menu is shown by programmatic means, supply Nothing.

-> IO () 

Popup a context menu where a button press occurred.

  • This function must be called in response to a button click. It opens the given menu at a place determined by the last emitted event (hence the requirement that this function is called as response to a button press signal).

messageDialogNew

Arguments

:: Maybe Window

Transient parent of the dialog (or none)

-> [DialogFlags] 
-> MessageType 
-> ButtonsType 
-> String

The text of the message

-> IO MessageDialog 

Create a new message dialog, which is a simple dialog with an icon indicating the dialog type (error, warning, etc.) and some text the user may want to see. When the user clicks a button a "response" signal is emitted with response IDs from ResponseType. See Dialog for more details.

on :: object -> Signal object callback -> callback -> IO (ConnectId object)

Perform an action in response to a signal.

Use it like this:

 on obj sig $ do
 ...

or if the signal handler takes any arguments:

 on obj sig $ \args -> do
 ...

onDestroy :: WidgetClass w => w -> IO () -> IO (ConnectId w)

The widget will be destroyed.

  • This is the last signal this widget will receive.

onSizeRequest :: WidgetClass w => w -> IO Requisition -> IO (ConnectId w)

Query the widget for the size it likes to have.

  • A parent container emits this signal to its child to query the needed height and width of the child. There is not guarantee that the widget will actually get this area.

data Packing

Packing parameters of a widget

  • The Packing parameter determines how the child behaves in the horizontal or vertical way in an HBox or VBox, respectively. PackNatural means the child is as big as it reqests. It will stay at the start of the end of a Box if there is more space available. All children packed with PackRepel will be padded on both sides with additional space. PackGrow will increase the size of a widget so that it covers the available space. A menu bar, for instance, should always stay at the top of a window and should only occupy as little space as possible. Hence it should be packed at the start of a VBox with the packing option PackNatural. The working area of a window (e.g. the text area in an editor) should expand when the window is resized. Here the packing option PackGrow is the right choice and it is irrelevant whether the main area is inserted at the start or the end of a box. Finally PackRepel is most useful in a window where no widget can make use of excess space. Examples include a dialog box without list boxes or text fields.

data Rectangle

Rectangle

  • Specifies x, y, width and height

Constructors

Rectangle Int Int Int Int 

renderWithDrawable

Arguments

:: DrawableClass drawable 
=> drawable

drawable - a Drawable

-> Render a

A newly created Cairo context.

-> IO a 

Creates a Cairo context for drawing to a Drawable.

data Requisition

Requisition

  • For widgetSizeRequest. The values represent the desired width and height of the widget.

Constructors

Requisition Int Int 

data ResponseId

Some constructors that can be used as response numbers for dialogs.

Constructors

ResponseNone

GTK returns this if a response widget has no response_id, or if the dialog gets programmatically hidden or destroyed.

ResponseReject

GTK won't return these unless you pass them in as the response for an action widget. They are for your convenience.

ResponseAccept

(as above)

ResponseDeleteEvent

If the dialog is deleted.

ResponseOk

"Ok" was pressed.

  • This value is returned from the "Ok" stock dialog button.
ResponseCancel

"Cancel" was pressed.

  • These value is returned from the "Cancel" stock dialog button.
ResponseClose

"Close" was pressed.

  • This value is returned from the "Close" stock dialog button.
ResponseYes

"Yes" was pressed.

  • This value is returned from the "Yes" stock dialog button.
ResponseNo

"No" was pressed.

  • This value is returned from the "No" stock dialog button.
ResponseApply

"Apply" was pressed.

  • This value is returned from the "Apply" stock dialog button.
ResponseHelp

"Help" was pressed.

  • This value is returned from the "Help" stock dialog button.
ResponseUser Int

A user-defined response

  • This value is returned from a user defined button

scrolledWindowNew

Arguments

:: Maybe Adjustment

hadjustment - Horizontal adjustment.

-> Maybe Adjustment

vadjustment - Vertical adjustment.

-> IO ScrolledWindow 

Creates a new scrolled window. The two arguments are the scrolled window's adjustments; these will be shared with the scrollbars and the child widget to keep the bars in sync with the child. Usually you want to pass Nothing for the adjustments, which will cause the scrolled window to create them for you.

scrolledWindowSetPolicy

Arguments

:: ScrolledWindowClass self 
=> self 
-> PolicyType

hscrollbarPolicy - Policy for horizontal bar.

-> PolicyType

vscrollbarPolicy - Policy for vertical bar.

-> IO () 

Sets the scrollbar policy for the horizontal and vertical scrollbars. The policy determines when the scrollbar should appear; it is a value from the PolicyType enumeration. If PolicyAlways, the scrollbar is always present; if PolicyNever, the scrollbar is never present; if PolicyAutomatic, the scrollbar is present only if needed (that is, if the slider part of the bar would be smaller than the trough - the display is larger than the page size).

statusbarGetContextId

Arguments

:: StatusbarClass self 
=> self 
-> String

contextDescription - textual description of what context the new message is being used in.

-> IO ContextId

returns an id that can be used to later remove entries ^ from the Statusbar.

Returns a new context identifier, given a description of the actual context. This id can be used to later remove entries form the Statusbar.

statusbarNew :: IO Statusbar

Creates a new Statusbar ready for messages.

statusbarPop

Arguments

:: StatusbarClass self 
=> self 
-> ContextId

contextId - the context identifier used when the message was added.

-> IO () 

Removes the topmost message that has the correct context.

statusbarPush

Arguments

:: StatusbarClass self 
=> self 
-> ContextId

contextId - the message's context id, as returned by statusbarGetContextId.

-> String

text - the message to add to the statusbar.

-> IO MessageId

returns the message's new message id for use with statusbarRemove.

Pushes a new message onto the Statusbar's stack. It will be displayed as long as it is on top of the stack.

vBoxNew

Arguments

:: Bool

homogeneous - True if all children are to be given equal space allotments.

-> Int

spacing - the number of pixels to place by default between children.

-> IO VBox 

Creates a new VBox.

class ObjectClass o => WidgetClass o

Instances

WidgetClass TipsQuery 
WidgetClass Item 
WidgetClass ListItem 
WidgetClass InputDialog 
WidgetClass CList 
WidgetClass CTree 
WidgetClass List 
WidgetClass Preview 
WidgetClass Widget 
WidgetClass HSV 
WidgetClass Misc 
WidgetClass Label 
WidgetClass AccelLabel 
WidgetClass Arrow 
WidgetClass Image 
WidgetClass Container 
WidgetClass ToolPalette 
WidgetClass ToolItemGroup 
WidgetClass Bin 
WidgetClass Alignment 
WidgetClass Frame 
WidgetClass AspectFrame 
WidgetClass Button 
WidgetClass ScaleButton 
WidgetClass VolumeButton 
WidgetClass LinkButton 
WidgetClass ToggleButton 
WidgetClass CheckButton 
WidgetClass RadioButton 
WidgetClass ColorButton 
WidgetClass FontButton 
WidgetClass OptionMenu 
WidgetClass MenuItem 
WidgetClass CheckMenuItem 
WidgetClass RadioMenuItem 
WidgetClass TearoffMenuItem 
WidgetClass ImageMenuItem 
WidgetClass SeparatorMenuItem 
WidgetClass Window 
WidgetClass Assistant 
WidgetClass OffscreenWindow 
WidgetClass Dialog 
WidgetClass AboutDialog 
WidgetClass ColorSelectionDialog 
WidgetClass FileSelection 
WidgetClass FileChooserDialog 
WidgetClass FontSelectionDialog 
WidgetClass MessageDialog 
WidgetClass Plug 
WidgetClass EventBox 
WidgetClass HandleBox 
WidgetClass ScrolledWindow 
WidgetClass Viewport 
WidgetClass Expander 
WidgetClass ComboBox 
WidgetClass ComboBoxEntry 
WidgetClass ToolItem 
WidgetClass ToolButton 
WidgetClass MenuToolButton 
WidgetClass ToggleToolButton 
WidgetClass RadioToolButton 
WidgetClass SeparatorToolItem 
WidgetClass Box 
WidgetClass ButtonBox 
WidgetClass HButtonBox 
WidgetClass VButtonBox 
WidgetClass VBox 
WidgetClass RecentChooserWidget 
WidgetClass ColorSelection 
WidgetClass FontSelection 
WidgetClass FileChooserWidget 
WidgetClass HBox 
WidgetClass InfoBar 
WidgetClass Combo 
WidgetClass FileChooserButton 
WidgetClass Statusbar 
WidgetClass Fixed 
WidgetClass Paned 
WidgetClass HPaned 
WidgetClass VPaned 
WidgetClass IconView 
WidgetClass Layout 
WidgetClass MenuShell 
WidgetClass Menu 
WidgetClass RecentChooserMenu 
WidgetClass MenuBar 
WidgetClass Notebook 
WidgetClass Socket 
WidgetClass Table 
WidgetClass TextView 
WidgetClass Toolbar 
WidgetClass TreeView 
WidgetClass Calendar 
WidgetClass CellView 
WidgetClass DrawingArea 
WidgetClass Spinner 
WidgetClass Entry 
WidgetClass SpinButton 
WidgetClass Ruler 
WidgetClass HRuler 
WidgetClass VRuler 
WidgetClass Range 
WidgetClass Scale 
WidgetClass HScale 
WidgetClass VScale 
WidgetClass Scrollbar 
WidgetClass HScrollbar 
WidgetClass VScrollbar 
WidgetClass Separator 
WidgetClass HSeparator 
WidgetClass VSeparator 
WidgetClass Invisible 
WidgetClass ProgressBar 

widgetAddEvents :: WidgetClass self => self -> [EventMask] -> IO ()

Enable event signals.

widgetClassPath

Arguments

:: WidgetClass self 
=> self 
-> IO (Int, String, String)

(pathLength, path, pathReversed) - length of the path, path string and reverse path string

Same as widgetPath, but always uses the name of a widget's type, never uses a custom name set with widgetSetName.

widgetDestroy :: WidgetClass self => self -> IO ()

Destroys a widget. Equivalent to objectDestroy.

When a widget is destroyed it will be removed from the screen and unrealized. When a widget is destroyed, it will break any references it holds to other objects.If the widget is inside a container, the widget will be removed from the container. The widget will be garbage collected (finalized) time after your last reference to the widget dissapears.

In most cases, only toplevel widgets (windows) require explicit destruction, because when you destroy a toplevel its children will be destroyed as well.

widgetGrabFocus :: WidgetClass self => self -> IO ()

Causes widget to have the keyboard focus for the Window it's inside. widget must be a focusable widget, such as a Entry; something like Frame won't work. (More precisely, it must have the widgetCanFocus flag set.)

widgetSetCanFocus :: WidgetClass self => self -> Bool -> IO ()

Set if this widget can receive keyboard input.

  • To use the keyPress 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.

widgetSetDoubleBuffered

Arguments

:: WidgetClass self 
=> self 
-> Bool

doubleBuffered - True to double-buffer a widget

-> IO () 

Widgets are double buffered by default; you can use this function to turn off the buffering. "Double buffered" simply means that drawWindowBeginPaintRegion and drawWindowEndPaint are called automatically around expose events sent to the widget. drawWindowBeginPaintRegion diverts all drawing to a widget's window to an offscreen buffer, and 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 drawWindowBeginPaint).

widgetSetName

Arguments

:: WidgetClass self 
=> self 
-> String

name - name for the widget

-> IO () 

Widgets can be named, which allows you to refer to them from a gtkrc file. You can apply a style to widgets with a particular name in the gtkrc file. See the documentation for gtkrc files.

Note that widget names are separated by periods in paths (see widgetPath), so names with embedded periods may cause confusion.

widgetSetSizeRequest

Arguments

:: WidgetClass self 
=> self 
-> Int

width - width widget should request, or -1 to unset

-> Int

height - height widget should request, or -1 to unset

-> IO () 

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, 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, 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."

widgetShow :: WidgetClass self => self -> IO ()

Flags a widget to be displayed. Any widget that isn't shown will not appear on the screen. If you want to show all the widgets in a container, it's easier to call widgetShowAll on the container, instead of individually showing the widgets.

Remember that you have to show the containers containing a widget, in addition to the widget itself, before it will appear onscreen.

When a toplevel container is shown, it is immediately realized and mapped; other shown widgets are realized and mapped when their toplevel container is realized and mapped.

widgetShowAll :: WidgetClass self => self -> IO ()

Recursively shows a widget, and any child widgets (if the widget is a container).

widgetSizeRequest :: WidgetClass self => self -> IO Requisition

This function is typically used when implementing a Container subclass. Obtains the preferred size of a widget. The container uses this information to arrange its child widgets and decide what size allocations to give them with widgetSizeAllocate.

You can also call this function from an application, with some caveats. Most notably, getting a size request requires the widget to be associated with a screen, because font information may be needed. Multihead-aware applications should keep this in mind.

Also remember that the size request is not necessarily the size a widget will actually be allocated.

widgetVisible :: WidgetClass self => Attr self Bool

Whether the widget is visible.

Default value: False

windowDeletable :: WindowClass self => Attr self Bool

Whether the window frame should have a close button.

Default values: True

  • Available since Gtk+ version 2.10

windowMove

Arguments

:: WindowClass self 
=> self 
-> Int

x - X coordinate to move window to

-> Int

y - Y coordinate to move window to

-> IO () 

Asks the window manager to move window to the given position. Window managers are free to ignore this; most window managers ignore requests for initial window positions (instead using a user-defined placement algorithm) and honor requests after the window has already been shown.

Note: the position is the position of the gravity-determined reference point for the window. The gravity determines two things: first, the location of the reference point in root window coordinates; and second, which point on the window is positioned at the reference point.

By default the gravity is GravityNorthWest, so the reference point is simply the x, y supplied to windowMove. The top-left corner of the window decorations (aka window frame or border) will be placed at x, y. Therefore, to position a window at the top left of the screen, you want to use the default gravity (which is GravityNorthWest) and move the window to 0,0.

To position a window at the bottom right corner of the screen, you would set GravitySouthEast, which means that the reference point is at x + the window width and y + the window height, and the bottom-right corner of the window border will be placed at that reference point. So, to place a window in the bottom right corner you would first set gravity to south east, then write: gtk_window_move (window, gdk_screen_width() - window_width, gdk_screen_height() - window_height).

The Extended Window Manager Hints specification at http://www.freedesktop.org/Standards/wm-spec has a nice table of gravities in the "implementation notes" section.

The windowGetPosition documentation may also be relevant.

windowNew :: IO Window

Create a new top level window.

windowPresent :: WindowClass self => self -> IO ()

Presents a window to the user. This may mean raising the window in the stacking order, deiconifying it, moving it to the current desktop, and/or giving it the keyboard focus, possibly dependent on the user's platform, window manager, and preferences.

If window is hidden, this function calls widgetShow as well.

This function should be used when the user tries to open a window that's already open. Say for example the preferences dialog is currently open, and the user chooses Preferences from the menu a second time; use windowPresent to move the already-open dialog where the user can see it.

If you are calling this function in response to a user interaction, it is preferable to use windowPresentWithTime.

windowSetDefaultSize

Arguments

:: WindowClass self 
=> self 
-> Int

height - height in pixels, or -1 to unset the default height

-> Int

width - width in pixels, or -1 to unset the default width

-> IO () 

Sets the default size of a window. If the window's "natural" size (its size request) is larger than the default, the default will be ignored. More generally, if the default size does not obey the geometry hints for the window (windowSetGeometryHints can be used to set these explicitly), the default size will be clamped to the nearest permitted size.

Unlike widgetSetSizeRequest, which sets a size request for a widget and thus would keep users from shrinking the window, this function only sets the initial size, just as if the user had resized the window themselves. Users can still shrink the window again as they normally would. Setting a default size of -1 means to use the "natural" default size (the size request of the window).

For more control over a window's initial size and how resizing works, investigate windowSetGeometryHints.

For some uses, windowResize is a more appropriate function. windowResize changes the current size of the window, rather than the size to be used on initial display. windowResize always affects the window itself, not the geometry widget.

The default size of a window only affects the first time a window is shown; if a window is hidden and re-shown, it will remember the size it had prior to hiding, rather than using the default size.

Windows can't actually be 0x0 in size, they must be at least 1x1, but passing 0 for width and height is OK, resulting in a 1x1 default size.

windowSetPosition :: WindowClass self => self -> WindowPosition -> IO ()

Sets a position constraint for this window. If the old or new constraint is WinPosCenterAlways, this will also cause the window to be repositioned to satisfy the new constraint.

windowSetTitle :: WindowClass self => self -> String -> IO ()

Sets the title of the Window. The title of a window will be displayed in its title bar; on the X Window System, the title bar is rendered by the window manager, so exactly how the title appears to users may vary according to a user's exact configuration. The title should help a user distinguish this window from other windows they may have open. A good title might include the application name and current document filename, for example.

windowTitle :: WindowClass self => Attr self String

The title of the window.

initGUI :: IO [String]

Initialize the GUI.

This must be called before any other function in the Gtk2Hs library.

This function initializes the GUI toolkit and parses all Gtk specific arguments. The remaining arguments are returned. If the initialization of the toolkit fails for whatever reason, an exception is thrown.

  • Throws: error "Cannot initialize GUI."
  • If you want to use Gtk2Hs and in a multi-threaded application then it is your obligation to ensure that all calls to Gtk+ happen in a single OS thread. If you want to make calls to Gtk2Hs functions from a Haskell thread other than the one that calls this functions and mainGUI then you will have to 'post' your GUI actions to the main GUI thread. You can do this using postGUISync or postGUIAsync. See also threadsEnter.

mainGUI :: IO ()

Run the Gtk+ main event loop.

mainQuit :: IO ()

Exit the main event loop.