Gtk2HsContentsIndex
Graphics.UI.Gtk.General.General
Portabilityportable (depends on GHC)
Stabilityprovisional
Maintainergtk2hs-users@lists.sourceforge.net
Contents
Initialisation
Support for OS threads
Main event loop
Less commonly used event loop functions
Grab widgets
Timeout and idle callbacks
Description
library initialization, main event loop, and events
Synopsis
initGUI :: IO [String]
unsafeInitGUIForThreadedRTS :: IO [String]
postGUISync :: IO a -> IO a
postGUIAsync :: IO () -> IO ()
mainGUI :: IO ()
mainQuit :: IO ()
eventsPending :: IO Int
mainLevel :: IO Int
mainIteration :: IO Bool
mainIterationDo :: Bool -> IO Bool
grabAdd :: WidgetClass wd => wd -> IO ()
grabGetCurrent :: IO (Maybe Widget)
grabRemove :: WidgetClass w => w -> IO ()
type Priority = Int
priorityLow :: Int
priorityDefaultIdle :: Int
priorityHighIdle :: Int
priorityDefault :: Int
priorityHigh :: Int
timeoutAdd :: IO Bool -> Int -> IO HandlerId
timeoutAddFull :: IO Bool -> Priority -> Int -> IO HandlerId
timeoutRemove :: HandlerId -> IO ()
idleAdd :: IO Bool -> Priority -> IO HandlerId
idleRemove :: HandlerId -> IO ()
inputAdd :: FD -> [IOCondition] -> Priority -> IO Bool -> IO HandlerId
inputRemove :: HandlerId -> IO ()
data IOCondition
type HandlerId = CUInt
Initialisation
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."
Support for OS threads
unsafeInitGUIForThreadedRTS :: IO [String]

Same as initGUI except that it prints no warning when used with GHC's threaded RTS.

If you want to use Gtk2Hs and the threaded RTS then it is your obligation to ensure that all calls to Gtk+ happen on 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.

postGUISync :: IO a -> IO a

Post an action to be run in the main GUI thread.

The current thread blocks until the action completes and the result is returned.

postGUIAsync :: IO () -> IO ()

Post an action to be run in the main GUI thread.

The current thread continues and does not wait for the result of the action.

Main event loop
mainGUI :: IO ()
Run the Gtk+ main event loop.
mainQuit :: IO ()
Exit the main event loop.
Less commonly used event loop functions
eventsPending :: IO Int
Inquire the number of events pending on the event queue
mainLevel :: IO Int

Inquire the main loop level.

  • Callbacks that take more time to process can call mainIteration to keep the GUI responsive. Each time the main loop is restarted this way, the main loop counter is increased. This function returns this counter.
mainIteration :: IO Bool

Process an event, block if necessary.

  • Returns True if mainQuit was called while processing the event.
mainIterationDo :: Bool -> IO Bool

Process a single event.

  • Called with True, this function behaves as mainIteration in that it waits until an event is available for processing. It will return immediately, if passed False.
  • Returns True if the mainQuit was called while processing the event.
Grab widgets
grabAdd :: WidgetClass wd => wd -> IO ()
add a grab widget
grabGetCurrent :: IO (Maybe Widget)
inquire current grab widget
grabRemove :: WidgetClass w => w -> IO ()
remove a grab widget
Timeout and idle callbacks
type Priority = Int
Priorities for installing callbacks.
priorityLow :: Int
priorityDefaultIdle :: Int
priorityHighIdle :: Int
priorityDefault :: Int
priorityHigh :: Int
timeoutAdd :: IO Bool -> Int -> IO HandlerId

Sets a function to be called at regular intervals, with the default priority priorityDefault. The function is called repeatedly until it returns False, after which point the timeout function will not be called again. The first call to the function will be at the end of the first interval.

Note that timeout functions may be delayed, due to the processing of other event sources. Thus they should not be relied on for precise timing. After each call to the timeout function, the time of the next timeout is recalculated based on the current time and the given interval (it does not try to 'catch up' time lost in delays).

timeoutAddFull :: IO Bool -> Priority -> Int -> IO HandlerId

Sets a function to be called at regular intervals, with the given priority. The function is called repeatedly until it returns False, after which point the timeout function will not be called again. The first call to the function will be at the end of the first interval.

Note that timeout functions may be delayed, due to the processing of other event sources. Thus they should not be relied on for precise timing. After each call to the timeout function, the time of the next timeout is recalculated based on the current time and the given interval (it does not try to 'catch up' time lost in delays).

timeoutRemove :: HandlerId -> IO ()
Remove a previously added timeout handler by its HandlerId.
idleAdd :: IO Bool -> Priority -> IO HandlerId

Add a callback that is called whenever the system is idle.

  • A priority can be specified via an integer. This should usually be priorityDefaultIdle.
  • If the function returns False it will be removed.
idleRemove :: HandlerId -> IO ()
Remove a previously added idle handler by its HandlerId.
inputAdd
:: FDa file descriptor
-> [IOCondition]the condition to watch for
-> Prioritythe priority of the event source
-> IO Boolthe function to call when the condition is satisfied. The function should return False if the event source should be removed.
-> IO HandlerIdthe event source id
Adds the file descriptor into the main event loop with the given priority.
inputRemove :: HandlerId -> IO ()
data IOCondition

Flags representing a condition to watch for on a file descriptor.

IOIn
There is data to read. [IOOut] Data can be written (without blocking). [IOPri] There is urgent data to read. [IOErr] Error condition. [IOHup] Hung up (the connection has been broken, usually for pipes and sockets). [IOInvalid] Invalid request. The file descriptor is not open.
show/hide Instances
type HandlerId = CUInt
Produced by Haddock version 0.8