| Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte | 
|---|---|
| License | LGPL-2.1 | 
| Maintainer | Iñaki García Etxebarria | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
GI.Gtk.Functions
Contents
- Methods
- accelGroupsActivate
 - accelGroupsFromObject
 - acceleratorGetDefaultModMask
 - acceleratorGetLabel
 - acceleratorGetLabelWithKeycode
 - acceleratorName
 - acceleratorNameWithKeycode
 - acceleratorParse
 - acceleratorParseWithKeycode
 - acceleratorSetDefaultModMask
 - acceleratorValid
 - alternativeDialogButtonOrder
 - bindingsActivate
 - bindingsActivateEvent
 - cairoShouldDrawWindow
 - cairoTransformToWindow
 - checkVersion
 - deviceGrabAdd
 - deviceGrabRemove
 - disableSetlocale
 - distributeNaturalAllocation
 - dragCancel
 - dragFinish
 - dragGetSourceWidget
 - dragSetIconDefault
 - dragSetIconGicon
 - dragSetIconName
 - dragSetIconPixbuf
 - dragSetIconStock
 - dragSetIconSurface
 - dragSetIconWidget
 - drawInsertionCursor
 - eventsPending
 - false
 - getBinaryAge
 - getCurrentEvent
 - getCurrentEventDevice
 - getCurrentEventState
 - getCurrentEventTime
 - getDebugFlags
 - getDefaultLanguage
 - getEventWidget
 - getInterfaceAge
 - getLocaleDirection
 - getMajorVersion
 - getMicroVersion
 - getMinorVersion
 - getOptionGroup
 - grabGetCurrent
 - init
 - initCheck
 - initWithArgs
 - keySnooperRemove
 - main
 - mainDoEvent
 - mainIteration
 - mainIterationDo
 - mainLevel
 - mainQuit
 - paintArrow
 - paintBox
 - paintBoxGap
 - paintCheck
 - paintDiamond
 - paintExpander
 - paintExtension
 - paintFlatBox
 - paintFocus
 - paintHandle
 - paintHline
 - paintLayout
 - paintOption
 - paintResizeGrip
 - paintShadow
 - paintShadowGap
 - paintSlider
 - paintSpinner
 - paintTab
 - paintVline
 - parseArgs
 - printRunPageSetupDialog
 - printRunPageSetupDialogAsync
 - propagateEvent
 - rcAddDefaultFile
 - rcFindModuleInPath
 - rcFindPixmapInPath
 - rcGetDefaultFiles
 - rcGetImModuleFile
 - rcGetImModulePath
 - rcGetModuleDir
 - rcGetStyle
 - rcGetStyleByPaths
 - rcGetThemeDir
 - rcParse
 - rcParseColor
 - rcParseColorFull
 - rcParsePriority
 - rcParseState
 - rcParseString
 - rcReparseAll
 - rcReparseAllForSettings
 - rcResetStyles
 - rcSetDefaultFiles
 - renderActivity
 - renderArrow
 - renderBackground
 - renderBackgroundGetClip
 - renderCheck
 - renderExpander
 - renderExtension
 - renderFocus
 - renderFrame
 - renderFrameGap
 - renderHandle
 - renderIcon
 - renderIconPixbuf
 - renderIconSurface
 - renderInsertionCursor
 - renderLayout
 - renderLine
 - renderOption
 - renderSlider
 - rgbToHsv
 - selectionAddTarget
 - selectionAddTargets
 - selectionClearTargets
 - selectionConvert
 - selectionOwnerSet
 - selectionOwnerSetForDisplay
 - selectionRemoveAll
 - setDebugFlags
 - showUri
 - showUriOnWindow
 - stockAdd
 - stockAddStatic
 - stockListIds
 - stockLookup
 - stockSetTranslateFunc
 - targetTableFree
 - targetTableNewFromList
 - targetsIncludeImage
 - targetsIncludeRichText
 - targetsIncludeText
 - targetsIncludeUri
 - testCreateSimpleWindow
 - testFindLabel
 - testFindSibling
 - testFindWidget
 - testListAllTypes
 - testRegisterAllTypes
 - testSliderGetValue
 - testSliderSetPerc
 - testSpinButtonClick
 - testTextGet
 - testTextSet
 - testWidgetClick
 - testWidgetSendKey
 - testWidgetWaitForDraw
 - treeGetRowDragData
 - treeSetRowDragData
 - true
 
 
Description
Synopsis
- accelGroupsActivate :: (HasCallStack, MonadIO m, IsObject a) => a -> Word32 -> [ModifierType] -> m Bool
 - accelGroupsFromObject :: (HasCallStack, MonadIO m, IsObject a) => a -> m [AccelGroup]
 - acceleratorGetDefaultModMask :: (HasCallStack, MonadIO m) => m [ModifierType]
 - acceleratorGetLabel :: (HasCallStack, MonadIO m) => Word32 -> [ModifierType] -> m Text
 - acceleratorGetLabelWithKeycode :: (HasCallStack, MonadIO m, IsDisplay a) => Maybe a -> Word32 -> Word32 -> [ModifierType] -> m Text
 - acceleratorName :: (HasCallStack, MonadIO m) => Word32 -> [ModifierType] -> m Text
 - acceleratorNameWithKeycode :: (HasCallStack, MonadIO m, IsDisplay a) => Maybe a -> Word32 -> Word32 -> [ModifierType] -> m Text
 - acceleratorParse :: (HasCallStack, MonadIO m) => Text -> m (Word32, [ModifierType])
 - acceleratorParseWithKeycode :: (HasCallStack, MonadIO m) => Text -> m (Word32, [Word32], [ModifierType])
 - acceleratorSetDefaultModMask :: (HasCallStack, MonadIO m) => [ModifierType] -> m ()
 - acceleratorValid :: (HasCallStack, MonadIO m) => Word32 -> [ModifierType] -> m Bool
 - alternativeDialogButtonOrder :: (HasCallStack, MonadIO m, IsScreen a) => Maybe a -> m Bool
 - bindingsActivate :: (HasCallStack, MonadIO m, IsObject a) => a -> Word32 -> [ModifierType] -> m Bool
 - bindingsActivateEvent :: (HasCallStack, MonadIO m, IsObject a) => a -> EventKey -> m Bool
 - cairoShouldDrawWindow :: (HasCallStack, MonadIO m, IsWindow a) => Context -> a -> m Bool
 - cairoTransformToWindow :: (HasCallStack, MonadIO m, IsWidget a, IsWindow b) => Context -> a -> b -> m ()
 - checkVersion :: (HasCallStack, MonadIO m) => Word32 -> Word32 -> Word32 -> m (Maybe Text)
 - deviceGrabAdd :: (HasCallStack, MonadIO m, IsWidget a, IsDevice b) => a -> b -> Bool -> m ()
 - deviceGrabRemove :: (HasCallStack, MonadIO m, IsWidget a, IsDevice b) => a -> b -> m ()
 - disableSetlocale :: (HasCallStack, MonadIO m) => m ()
 - distributeNaturalAllocation :: (HasCallStack, MonadIO m) => Int32 -> [RequestedSize] -> m (Int32, [RequestedSize])
 - dragCancel :: (HasCallStack, MonadIO m, IsDragContext a) => a -> m ()
 - dragFinish :: (HasCallStack, MonadIO m, IsDragContext a) => a -> Bool -> Bool -> Word32 -> m ()
 - dragGetSourceWidget :: (HasCallStack, MonadIO m, IsDragContext a) => a -> m (Maybe Widget)
 - dragSetIconDefault :: (HasCallStack, MonadIO m, IsDragContext a) => a -> m ()
 - dragSetIconGicon :: (HasCallStack, MonadIO m, IsDragContext a, IsIcon b) => a -> b -> Int32 -> Int32 -> m ()
 - dragSetIconName :: (HasCallStack, MonadIO m, IsDragContext a) => a -> Text -> Int32 -> Int32 -> m ()
 - dragSetIconPixbuf :: (HasCallStack, MonadIO m, IsDragContext a, IsPixbuf b) => a -> b -> Int32 -> Int32 -> m ()
 - dragSetIconStock :: (HasCallStack, MonadIO m, IsDragContext a) => a -> Text -> Int32 -> Int32 -> m ()
 - dragSetIconSurface :: (HasCallStack, MonadIO m, IsDragContext a) => a -> Surface -> m ()
 - dragSetIconWidget :: (HasCallStack, MonadIO m, IsDragContext a, IsWidget b) => a -> b -> Int32 -> Int32 -> m ()
 - drawInsertionCursor :: (HasCallStack, MonadIO m, IsWidget a) => a -> Context -> Rectangle -> Bool -> TextDirection -> Bool -> m ()
 - eventsPending :: (HasCallStack, MonadIO m) => m Bool
 - false :: (HasCallStack, MonadIO m) => m Bool
 - getBinaryAge :: (HasCallStack, MonadIO m) => m Word32
 - getCurrentEvent :: (HasCallStack, MonadIO m) => m (Maybe Event)
 - getCurrentEventDevice :: (HasCallStack, MonadIO m) => m (Maybe Device)
 - getCurrentEventState :: (HasCallStack, MonadIO m) => m (Bool, [ModifierType])
 - getCurrentEventTime :: (HasCallStack, MonadIO m) => m Word32
 - getDebugFlags :: (HasCallStack, MonadIO m) => m Word32
 - getDefaultLanguage :: (HasCallStack, MonadIO m) => m Language
 - getEventWidget :: (HasCallStack, MonadIO m) => Event -> m (Maybe Widget)
 - getInterfaceAge :: (HasCallStack, MonadIO m) => m Word32
 - getLocaleDirection :: (HasCallStack, MonadIO m) => m TextDirection
 - getMajorVersion :: (HasCallStack, MonadIO m) => m Word32
 - getMicroVersion :: (HasCallStack, MonadIO m) => m Word32
 - getMinorVersion :: (HasCallStack, MonadIO m) => m Word32
 - getOptionGroup :: (HasCallStack, MonadIO m) => Bool -> m OptionGroup
 - grabGetCurrent :: (HasCallStack, MonadIO m) => m (Maybe Widget)
 - init :: (HasCallStack, MonadIO m) => Maybe [Text] -> m (Maybe [Text])
 - initCheck :: (HasCallStack, MonadIO m) => Maybe [Text] -> m (Bool, Maybe [Text])
 - initWithArgs :: (HasCallStack, MonadIO m) => Maybe [Text] -> Maybe Text -> [OptionEntry] -> Maybe Text -> m (Maybe [Text])
 - keySnooperRemove :: (HasCallStack, MonadIO m) => Word32 -> m ()
 - main :: (HasCallStack, MonadIO m) => m ()
 - mainDoEvent :: (HasCallStack, MonadIO m) => Event -> m ()
 - mainIteration :: (HasCallStack, MonadIO m) => m Bool
 - mainIterationDo :: (HasCallStack, MonadIO m) => Bool -> m Bool
 - mainLevel :: (HasCallStack, MonadIO m) => m Word32
 - mainQuit :: (HasCallStack, MonadIO m) => m ()
 - paintArrow :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> ArrowType -> Bool -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintBox :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintBoxGap :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> PositionType -> Int32 -> Int32 -> m ()
 - paintCheck :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintDiamond :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintExpander :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> ExpanderStyle -> m ()
 - paintExtension :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> PositionType -> m ()
 - paintFlatBox :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintFocus :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintHandle :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> Orientation -> m ()
 - paintHline :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> m ()
 - paintLayout :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b, IsLayout c) => a -> Context -> StateType -> Bool -> Maybe b -> Maybe Text -> Int32 -> Int32 -> c -> m ()
 - paintOption :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintResizeGrip :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> Maybe b -> Maybe Text -> WindowEdge -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintShadow :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintShadowGap :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> PositionType -> Int32 -> Int32 -> m ()
 - paintSlider :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> Orientation -> m ()
 - paintSpinner :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> Maybe b -> Maybe Text -> Word32 -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintTab :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> ShadowType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
 - paintVline :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) => a -> Context -> StateType -> Maybe b -> Maybe Text -> Int32 -> Int32 -> Int32 -> m ()
 - parseArgs :: (HasCallStack, MonadIO m) => [Text] -> m (Bool, [Text])
 - printRunPageSetupDialog :: (HasCallStack, MonadIO m, IsWindow a, IsPageSetup b, IsPrintSettings c) => Maybe a -> Maybe b -> c -> m PageSetup
 - printRunPageSetupDialogAsync :: (HasCallStack, MonadIO m, IsWindow a, IsPageSetup b, IsPrintSettings c) => Maybe a -> Maybe b -> c -> PageSetupDoneFunc -> m ()
 - propagateEvent :: (HasCallStack, MonadIO m, IsWidget a) => a -> Event -> m ()
 - rcAddDefaultFile :: (HasCallStack, MonadIO m) => [Char] -> m ()
 - rcFindModuleInPath :: (HasCallStack, MonadIO m) => Text -> m [Char]
 - rcFindPixmapInPath :: (HasCallStack, MonadIO m, IsSettings a) => a -> Scanner -> Text -> m [Char]
 - rcGetDefaultFiles :: (HasCallStack, MonadIO m) => m [[Char]]
 - rcGetImModuleFile :: (HasCallStack, MonadIO m) => m [Char]
 - rcGetImModulePath :: (HasCallStack, MonadIO m) => m [Char]
 - rcGetModuleDir :: (HasCallStack, MonadIO m) => m [Char]
 - rcGetStyle :: (HasCallStack, MonadIO m, IsWidget a) => a -> m Style
 - rcGetStyleByPaths :: (HasCallStack, MonadIO m, IsSettings a) => a -> Maybe Text -> Maybe Text -> GType -> m (Maybe Style)
 - rcGetThemeDir :: (HasCallStack, MonadIO m) => m Text
 - rcParse :: (HasCallStack, MonadIO m) => Text -> m ()
 - rcParseColor :: (HasCallStack, MonadIO m) => Scanner -> m (Word32, Color)
 - rcParseColorFull :: (HasCallStack, MonadIO m, IsRcStyle a) => Scanner -> Maybe a -> m (Word32, Color)
 - rcParsePriority :: (HasCallStack, MonadIO m) => Scanner -> PathPriorityType -> m Word32
 - rcParseState :: (HasCallStack, MonadIO m) => Scanner -> m (Word32, StateType)
 - rcParseString :: (HasCallStack, MonadIO m) => Text -> m ()
 - rcReparseAll :: (HasCallStack, MonadIO m) => m Bool
 - rcReparseAllForSettings :: (HasCallStack, MonadIO m, IsSettings a) => a -> Bool -> m Bool
 - rcResetStyles :: (HasCallStack, MonadIO m, IsSettings a) => a -> m ()
 - rcSetDefaultFiles :: (HasCallStack, MonadIO m) => [[Char]] -> m ()
 - renderActivity :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderArrow :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderBackground :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderBackgroundGetClip :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Double -> Double -> Double -> Double -> m Rectangle
 - renderCheck :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderExpander :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderExtension :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> PositionType -> m ()
 - renderFocus :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderFrame :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderFrameGap :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> PositionType -> Double -> Double -> m ()
 - renderHandle :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderIcon :: (HasCallStack, MonadIO m, IsStyleContext a, IsPixbuf b) => a -> Context -> b -> Double -> Double -> m ()
 - renderIconPixbuf :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> IconSource -> Int32 -> m Pixbuf
 - renderIconSurface :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Surface -> Double -> Double -> m ()
 - renderInsertionCursor :: (HasCallStack, MonadIO m, IsStyleContext a, IsLayout b) => a -> Context -> Double -> Double -> b -> Int32 -> Direction -> m ()
 - renderLayout :: (HasCallStack, MonadIO m, IsStyleContext a, IsLayout b) => a -> Context -> Double -> Double -> b -> m ()
 - renderLine :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderOption :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> m ()
 - renderSlider :: (HasCallStack, MonadIO m, IsStyleContext a) => a -> Context -> Double -> Double -> Double -> Double -> Orientation -> m ()
 - rgbToHsv :: (HasCallStack, MonadIO m) => Double -> Double -> Double -> m (Double, Double, Double)
 - selectionAddTarget :: (HasCallStack, MonadIO m, IsWidget a) => a -> Atom -> Atom -> Word32 -> m ()
 - selectionAddTargets :: (HasCallStack, MonadIO m, IsWidget a) => a -> Atom -> [TargetEntry] -> m ()
 - selectionClearTargets :: (HasCallStack, MonadIO m, IsWidget a) => a -> Atom -> m ()
 - selectionConvert :: (HasCallStack, MonadIO m, IsWidget a) => a -> Atom -> Atom -> Word32 -> m Bool
 - selectionOwnerSet :: (HasCallStack, MonadIO m, IsWidget a) => Maybe a -> Atom -> Word32 -> m Bool
 - selectionOwnerSetForDisplay :: (HasCallStack, MonadIO m, IsDisplay a, IsWidget b) => a -> Maybe b -> Atom -> Word32 -> m Bool
 - selectionRemoveAll :: (HasCallStack, MonadIO m, IsWidget a) => a -> m ()
 - setDebugFlags :: (HasCallStack, MonadIO m) => Word32 -> m ()
 - showUri :: (HasCallStack, MonadIO m, IsScreen a) => Maybe a -> Text -> Word32 -> m ()
 - showUriOnWindow :: (HasCallStack, MonadIO m, IsWindow a) => Maybe a -> Text -> Word32 -> m ()
 - stockAdd :: (HasCallStack, MonadIO m) => [StockItem] -> m ()
 - stockAddStatic :: (HasCallStack, MonadIO m) => [StockItem] -> m ()
 - stockListIds :: (HasCallStack, MonadIO m) => m [Text]
 - stockLookup :: (HasCallStack, MonadIO m) => Text -> m (Bool, StockItem)
 - stockSetTranslateFunc :: (HasCallStack, MonadIO m) => Text -> TranslateFunc -> m ()
 - targetTableFree :: (HasCallStack, MonadIO m) => [TargetEntry] -> m ()
 - targetTableNewFromList :: (HasCallStack, MonadIO m) => TargetList -> m [TargetEntry]
 - targetsIncludeImage :: (HasCallStack, MonadIO m) => [Atom] -> Bool -> m Bool
 - targetsIncludeRichText :: (HasCallStack, MonadIO m, IsTextBuffer a) => [Atom] -> a -> m Bool
 - targetsIncludeText :: (HasCallStack, MonadIO m) => [Atom] -> m Bool
 - targetsIncludeUri :: (HasCallStack, MonadIO m) => [Atom] -> m Bool
 - testCreateSimpleWindow :: (HasCallStack, MonadIO m) => Text -> Text -> m Widget
 - testFindLabel :: (HasCallStack, MonadIO m, IsWidget a) => a -> Text -> m Widget
 - testFindSibling :: (HasCallStack, MonadIO m, IsWidget a) => a -> GType -> m Widget
 - testFindWidget :: (HasCallStack, MonadIO m, IsWidget a) => a -> Text -> GType -> m (Maybe Widget)
 - testListAllTypes :: (HasCallStack, MonadIO m) => m ([GType], Word32)
 - testRegisterAllTypes :: (HasCallStack, MonadIO m) => m ()
 - testSliderGetValue :: (HasCallStack, MonadIO m, IsWidget a) => a -> m Double
 - testSliderSetPerc :: (HasCallStack, MonadIO m, IsWidget a) => a -> Double -> m ()
 - testSpinButtonClick :: (HasCallStack, MonadIO m, IsSpinButton a) => a -> Word32 -> Bool -> m Bool
 - testTextGet :: (HasCallStack, MonadIO m, IsWidget a) => a -> m Text
 - testTextSet :: (HasCallStack, MonadIO m, IsWidget a) => a -> Text -> m ()
 - testWidgetClick :: (HasCallStack, MonadIO m, IsWidget a) => a -> Word32 -> [ModifierType] -> m Bool
 - testWidgetSendKey :: (HasCallStack, MonadIO m, IsWidget a) => a -> Word32 -> [ModifierType] -> m Bool
 - testWidgetWaitForDraw :: (HasCallStack, MonadIO m, IsWidget a) => a -> m ()
 - treeGetRowDragData :: (HasCallStack, MonadIO m) => SelectionData -> m (Bool, Maybe TreeModel, Maybe TreePath)
 - treeSetRowDragData :: (HasCallStack, MonadIO m, IsTreeModel a) => SelectionData -> a -> TreePath -> m Bool
 - true :: (HasCallStack, MonadIO m) => m Bool
 
Methods
accelGroupsActivate
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Bool | Returns:   | 
Finds the first accelerator in any AccelGroup attached
 to object that matches accelKey and accelMods, and
 activates that accelerator.
accelGroupsFromObject
accelGroupsFromObject Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | |
| -> m [AccelGroup] | Returns: a list of
     all accel groups which are attached to   | 
Gets a list of all accel groups which are attached to object.
acceleratorGetDefaultModMask
acceleratorGetDefaultModMask Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m [ModifierType] | Returns: the default accelerator modifier mask  | 
Gets the modifier mask.
The modifier mask determines which modifiers are considered significant
 for keyboard accelerators. See acceleratorSetDefaultModMask.
acceleratorGetLabel
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Text | Returns: a newly-allocated string representing the accelerator.  | 
Converts an accelerator keyval and modifier mask into a string which can be used to represent the accelerator to the user.
Since: 2.6
acceleratorGetLabelWithKeycode
acceleratorGetLabelWithKeycode Source #
Arguments
| :: (HasCallStack, MonadIO m, IsDisplay a) | |
| => Maybe a | |
| -> Word32 | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Text | Returns: a newly-allocated string representing the accelerator.  | 
Converts an accelerator keyval and modifier mask
 into a (possibly translated) string that can be displayed to
 a user, similarly to acceleratorGetLabel, but handling
 keycodes.
This is only useful for system-level components, applications
 should use acceleratorParse instead.
Since: 3.4
acceleratorName
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Text | Returns: a newly-allocated accelerator name  | 
Converts an accelerator keyval and modifier mask into a string
 parseable by acceleratorParse. For example, if you pass in
 KEY_q and GDK_CONTROL_MASK, this function returns “<Control>q”.
If you need to display accelerators in the user interface,
 see acceleratorGetLabel.
acceleratorNameWithKeycode
acceleratorNameWithKeycode Source #
Arguments
| :: (HasCallStack, MonadIO m, IsDisplay a) | |
| => Maybe a | |
| -> Word32 | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Text | Returns: a newly allocated accelerator name.  | 
Converts an accelerator keyval and modifier mask
 into a string parseable by acceleratorParseWithKeycode,
 similarly to acceleratorName but handling keycodes.
 This is only useful for system-level components, applications
 should use acceleratorParse instead.
Since: 3.4
acceleratorParse
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
  | 
| -> m (Word32, [ModifierType]) | 
Parses a string representing an accelerator. The format looks like “<Control>a” or “<Shift><Alt>F1” or “<Release>z” (the last one is for key release).
The parser is fairly liberal and allows lower or upper case, and also
 abbreviations such as “<Ctl>” and “<Ctrl>”. Key names are parsed using
 keyvalFromName. For character keys the name is not the symbol,
 but the lowercase name, e.g. one would use “<Ctrl>minus” instead of
 “<Ctrl>-”.
If the parse fails, acceleratorKey and acceleratorMods will
 be set to 0 (zero).
acceleratorParseWithKeycode
acceleratorParseWithKeycode Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
  | 
| -> m (Word32, [Word32], [ModifierType]) | 
Parses a string representing an accelerator, similarly to
 acceleratorParse but handles keycodes as well. This is only
 useful for system-level components, applications should use
 acceleratorParse instead.
If acceleratorCodes is given and the result stored in it is non-Nothing,
 the result must be freed with free.
If a keycode is present in the accelerator and no acceleratorCodes
 is given, the parse will fail.
If the parse fails, acceleratorKey, acceleratorMods and
 acceleratorCodes will be set to 0 (zero).
Since: 3.4
acceleratorSetDefaultModMask
acceleratorSetDefaultModMask Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [ModifierType] | 
  | 
| -> m () | 
Sets the modifiers that will be considered significant for keyboard
 accelerators. The default mod mask depends on the GDK backend in use,
 but will typically include GDK_CONTROL_MASK | GDK_SHIFT_MASK |
 GDK_MOD1_MASK | GDK_SUPER_MASK | GDK_HYPER_MASK | GDK_META_MASK.
 In other words, Control, Shift, Alt, Super, Hyper and Meta. Other
 modifiers will by default be ignored by AccelGroup.
You must include at least the three modifiers Control, Shift and Alt in any value you pass to this function.
The default mod mask should be changed on application startup, before using any accelerator groups.
acceleratorValid
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Bool | Returns:   | 
Determines whether a given keyval and modifier mask constitute
 a valid keyboard accelerator. For example, the KEY_a keyval
 plus GDK_CONTROL_MASK is valid - this is a “Ctrl+a” accelerator.
 But, you can't, for instance, use the KEY_Control_L keyval
 as an accelerator.
alternativeDialogButtonOrder
alternativeDialogButtonOrder Source #
Arguments
| :: (HasCallStack, MonadIO m, IsScreen a) | |
| => Maybe a | |
| -> m Bool | Returns: Whether the alternative button order should be used  | 
Deprecated: (Since version 3.10)Deprecated
Returns True if dialogs are expected to use an alternative
 button order on the screen screen. See
 gtk_dialog_set_alternative_button_order() for more details
 about alternative button order.
If you need to use this function, you should probably connect
 to the notify:gtk-alternative-button-order signal on the
 Settings object associated to screen, in order to be
 notified if the button order setting changes.
Since: 2.6
bindingsActivate
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Bool | Returns:   | 
Find a key binding matching keyval and modifiers and activate the
 binding on object.
bindingsActivateEvent
bindingsActivateEvent Source #
Arguments
| :: (HasCallStack, MonadIO m, IsObject a) | |
| => a | 
  | 
| -> EventKey | 
  | 
| -> m Bool | Returns:   | 
Looks up key bindings for object to find one matching
 event, and if one was found, activate it.
Since: 2.4
cairoShouldDrawWindow
cairoShouldDrawWindow Source #
Arguments
| :: (HasCallStack, MonadIO m, IsWindow a) | |
| => Context | 
  | 
| -> a | 
  | 
| -> m Bool | Returns:   | 
This function is supposed to be called in draw
 implementations for widgets that support multiple windows.
 cr must be untransformed from invoking of the draw function.
 This function will return True if the contents of the given
 window are supposed to be drawn and False otherwise. Note
 that when the drawing was not initiated by the windowing
 system this function will return True for all windows, so
 you need to draw the bottommost window first. Also, do not
 use “else if” statements to check which window should be drawn.
Since: 3.0
cairoTransformToWindow
cairoTransformToWindow Source #
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a, IsWindow b) | |
| => Context | 
  | 
| -> a | 
  | 
| -> b | 
  | 
| -> m () | 
Transforms the given cairo context cr that from widget-relative
 coordinates to window-relative coordinates.
 If the widget’s window is not an ancestor of window, no
 modification will be applied.
This is the inverse to the transformation GTK applies when preparing an expose event to be emitted with the draw signal. It is intended to help porting multiwindow widgets from GTK+ 2 to the rendering architecture of GTK+ 3.
Since: 3.0
checkVersion
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
  | 
| -> Word32 | 
  | 
| -> Word32 | 
  | 
| -> m (Maybe Text) | Returns:   | 
Checks that the GTK+ library in use is compatible with the
 given version. Generally you would pass in the constants
 MAJOR_VERSION, MINOR_VERSION, MICRO_VERSION
 as the three arguments to this function; that produces
 a check that the library in use is compatible with
 the version of GTK+ the application or module was compiled
 against.
Compatibility is defined by two things: first the version
 of the running library is newer than the version
 requiredMajor.required_minor.requiredMicro. Second
 the running library must be binary compatible with the
 version requiredMajor.required_minor.requiredMicro
 (same major version.)
This function is primarily for GTK+ modules; the module
 can call this function to check that it wasn’t loaded
 into an incompatible version of GTK+. However, such a
 check isn’t completely reliable, since the module may be
 linked against an old version of GTK+ and calling the
 old version of checkVersion, but still get loaded
 into an application using a newer version of GTK+.
deviceGrabAdd
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a, IsDevice b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Bool | 
  | 
| -> m () | 
Adds a GTK+ grab on device, so all the events on device and its
 associated pointer or keyboard (if any) are delivered to widget.
 If the blockOthers parameter is True, any other devices will be
 unable to interact with widget during the grab.
Since: 3.0
deviceGrabRemove
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a, IsDevice b) | |
| => a | 
  | 
| -> b | 
  | 
| -> m () | 
Removes a device grab from the given widget.
You have to pair calls to deviceGrabAdd and
 deviceGrabRemove.
Since: 3.0
disableSetlocale
disableSetlocale :: (HasCallStack, MonadIO m) => m () Source #
Prevents init, initCheck, initWithArgs and
 parseArgs from automatically
 calling setlocale (LC_ALL, ""). You would
 want to use this function if you wanted to set the locale for
 your program to something other than the user’s locale, or if
 you wanted to set different values for different locale categories.
Most programs should not need to call this function.
distributeNaturalAllocation
distributeNaturalAllocation Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Int32 | 
  | 
| -> [RequestedSize] | 
  | 
| -> m (Int32, [RequestedSize]) | Returns: The remainder of   | 
Distributes extraSpace to child sizes by bringing smaller
 children up to natural size first.
The remaining space will be added to the minimumSize member of the
 GtkRequestedSize struct. If all sizes reach their natural size then
 the remaining space is returned.
dragCancel
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a) | |
| => a | 
  | 
| -> m () | 
Cancels an ongoing drag operation on the source side.
If you want to be able to cancel a drag operation in this way,
 you need to keep a pointer to the drag context, either from an
 explicit call to widgetDragBeginWithCoordinates, or by
 connecting to dragBegin.
If context does not refer to an ongoing drag operation, this
 function does nothing.
If a drag is cancelled in this way, the result argument of
 dragFailed is set to gTKDRAGRESULTERROR.
Since: 3.16
dragFinish
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a) | |
| => a | 
  | 
| -> Bool | 
  | 
| -> Bool | 
  | 
| -> Word32 | 
  | 
| -> m () | 
Informs the drag source that the drop is finished, and that the data of the drag will no longer be required.
dragGetSourceWidget
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a) | |
| => a | 
  | 
| -> m (Maybe Widget) | Returns: if the drag is occurring
     within a single application, a pointer to the source widget.
     Otherwise,   | 
Determines the source widget for a drag.
dragSetIconDefault
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a) | |
| => a | 
  | 
| -> m () | 
Sets the icon for a particular drag to the default icon.
dragSetIconGicon
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a, IsIcon b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Sets the icon for a given drag from the given icon.
 See the documentation for dragSetIconName
 for more details about using icons in drag and drop.
Since: 3.2
dragSetIconName
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a) | |
| => a | 
  | 
| -> Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Sets the icon for a given drag from a named themed icon. See
 the docs for IconTheme for more details. Note that the
 size of the icon depends on the icon theme (the icon is
 loaded at the symbolic size GTK_ICON_SIZE_DND), thus
 hotX and hotY have to be used with care.
Since: 2.8
dragSetIconPixbuf
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a, IsPixbuf b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Sets pixbuf as the icon for a given drag.
dragSetIconStock
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a) | |
| => a | 
  | 
| -> Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.10)Use dragSetIconName instead.
Sets the icon for a given drag from a stock ID.
dragSetIconSurface
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a) | |
| => a | 
  | 
| -> Surface | 
  | 
| -> m () | 
Sets surface as the icon for a given drag. GTK+ retains
 references for the arguments, and will release them when
 they are no longer needed.
To position the surface relative to the mouse, use
 cairo_surface_set_device_offset() on surface. The mouse
 cursor will be positioned at the (0,0) coordinate of the
 surface.
dragSetIconWidget
Arguments
| :: (HasCallStack, MonadIO m, IsDragContext a, IsWidget b) | |
| => a | 
  | 
| -> b | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Changes the icon for drag operation to a given widget. GTK+ will not destroy the widget, so if you don’t want it to persist, you should connect to the “drag-end” signal and destroy it yourself.
drawInsertionCursor
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Rectangle | 
  | 
| -> Bool | 
  | 
| -> TextDirection | 
  | 
| -> Bool | 
  | 
| -> m () | 
Deprecated: (Since version 3.4)Use renderInsertionCursor instead.
Draws a text caret on cr at location. This is not a style function
 but merely a convenience function for drawing the standard cursor shape.
Since: 3.0
eventsPending
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Bool | Returns:   | 
Checks if any events are pending.
This can be used to update the UI and invoke timeouts etc. while doing some time intensive computation.
Updating the UI during a long computation
C code
// computation going on... while (gtk_events_pending ()) gtk_main_iteration (); // ...computation continued
false
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Bool | Returns:   | 
Analogical to true, this function does nothing
 but always returns False.
getBinaryAge
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: the binary age of the GTK+ library  | 
Returns the binary age as passed to libtool
 when building the GTK+ library the process is running against.
 If libtool means nothing to you, don't
 worry about it.
Since: 3.0
getCurrentEvent
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m (Maybe Event) | Returns: a copy of the current event, or
       | 
Obtains a copy of the event currently being processed by GTK+.
For example, if you are handling a clicked signal,
 the current event will be the EventButton that triggered
 the clicked signal.
getCurrentEventDevice
getCurrentEventDevice Source #
If there is a current event and it has a device, return that
 device, otherwise return Nothing.
getCurrentEventState
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m (Bool, [ModifierType]) | Returns:   | 
If there is a current event and it has a state field, place
 that state field in state and return True, otherwise return
 False.
getCurrentEventTime
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: the timestamp from the current event,
     or   | 
If there is a current event and it has a timestamp,
 return that timestamp, otherwise return CURRENT_TIME.
getDebugFlags
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: the GTK+ debug flags.  | 
Returns the GTK+ debug flags.
This function is intended for GTK+ modules that want to adjust their debug output based on GTK+ debug flags.
getDefaultLanguage
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Language | Returns: the default language as a   | 
Returns the Language for the default language currently in
 effect. (Note that this can change over the life of an
 application.) The default language is derived from the current
 locale. It determines, for example, whether GTK+ uses the
 right-to-left or left-to-right text direction.
This function is equivalent to languageGetDefault.
 See that function for details.
getEventWidget
getInterfaceAge
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: the interface age of the GTK+ library  | 
Returns the interface age as passed to libtool
 when building the GTK+ library the process is running against.
 If libtool means nothing to you, don't
 worry about it.
Since: 3.0
getLocaleDirection
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m TextDirection | Returns: the   | 
Get the direction of the current locale. This is the expected reading direction for text and UI.
This function depends on the current locale being set with
 setlocale() and will default to setting the TextDirectionLtr
 direction otherwise. TextDirectionNone will never be returned.
GTK+ sets the default text direction according to the locale
 during init, and you should normally use
 widgetGetDirection or widgetGetDefaultDirection
 to obtain the current direcion.
This function is only needed rare cases when the locale is changed after GTK+ has already been initialized. In this case, you can use it to update the default text direction as follows:
C code
setlocale (LC_ALL, new_locale); direction = gtk_get_locale_direction (); gtk_widget_set_default_direction (direction);
Since: 3.12
getMajorVersion
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: the major version number of the GTK+ library  | 
Returns the major version number of the GTK+ library. (e.g. in GTK+ version 3.1.5 this is 3.)
This function is in the library, so it represents the GTK+ library
 your code is running against. Contrast with the MAJOR_VERSION
 macro, which represents the major version of the GTK+ headers you
 have included when compiling your code.
Since: 3.0
getMicroVersion
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: the micro version number of the GTK+ library  | 
Returns the micro version number of the GTK+ library. (e.g. in GTK+ version 3.1.5 this is 5.)
This function is in the library, so it represents the GTK+ library
 your code is are running against. Contrast with the
 MICRO_VERSION macro, which represents the micro version of the
 GTK+ headers you have included when compiling your code.
Since: 3.0
getMinorVersion
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: the minor version number of the GTK+ library  | 
Returns the minor version number of the GTK+ library. (e.g. in GTK+ version 3.1.5 this is 1.)
This function is in the library, so it represents the GTK+ library
 your code is are running against. Contrast with the
 MINOR_VERSION macro, which represents the minor version of the
 GTK+ headers you have included when compiling your code.
Since: 3.0
getOptionGroup
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Bool | 
  | 
| -> m OptionGroup | Returns: a   | 
Returns a OptionGroup for the commandline arguments recognized
 by GTK+ and GDK.
You should add this group to your OptionContext
 with optionContextAddGroup, if you are using
 optionContextParse to parse your commandline arguments.
Since: 2.6
grabGetCurrent
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m (Maybe Widget) | Returns: The widget which currently
     has the grab or   | 
Queries the current grab of the default window group.
init
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Maybe [Text] | 
  | 
| -> m (Maybe [Text]) | 
Call this function before using any other GTK+ functions in your GUI applications. It will initialize everything needed to operate the toolkit and parses some standard command line options.
Although you are expected to pass the argc, argv parameters from main() to
 this function, it is possible to pass Nothing if argv is not available or
 commandline handling is not required.
argc and argv are adjusted accordingly so your own code will
 never see those standard arguments.
Note that there are some alternative ways to initialize GTK+:
 if you are calling parseArgs, initCheck,
 initWithArgs or optionContextParse with
 the option group returned by getOptionGroup,
 you don’t have to call init.
And if you are using Application, you don't have to call any of the
 initialization functions either; the Application::startup handler
 does it for you.
This function will terminate your program if it was unable to
 initialize the windowing system for some reason. If you want
 your program to fall back to a textual interface you want to
 call initCheck instead.
Since 2.18, GTK+ calls signal (SIGPIPE, SIG_IGN)
 during initialization, to ignore SIGPIPE signals, since these are
 almost never wanted in graphical applications. If you do need to
 handle SIGPIPE for some reason, reset the handler after init,
 but notice that other libraries (e.g. libdbus or gvfs) might do
 similar things.
initCheck
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Maybe [Text] | 
  | 
| -> m (Bool, Maybe [Text]) | Returns:   | 
This function does the same work as init with only a single
 change: It does not terminate the program if the commandline
 arguments couldn’t be parsed or the windowing system can’t be
 initialized. Instead it returns False on failure.
This way the application can fall back to some other means of communication with the user - for example a curses or command line interface.
initWithArgs
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Maybe [Text] | 
  | 
| -> Maybe Text | 
  | 
| -> [OptionEntry] | 
  | 
| -> Maybe Text | 
  | 
| -> m (Maybe [Text]) | (Can throw   | 
This function does the same work as initCheck.
 Additionally, it allows you to add your own commandline options,
 and it automatically generates nicely formatted
 --help output. Note that your program will
 be terminated after writing out the help output.
Since: 2.6
keySnooperRemove
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Word32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.4)Key snooping should not be done. Events should be handled by widgets.
Removes the key snooper function with the given id.
main
main :: (HasCallStack, MonadIO m) => m () Source #
mainDoEvent
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Event | 
  | 
| -> m () | 
Processes a single GDK event.
This is public only to allow filtering of events between GDK and GTK+. You will not usually need to call this function directly.
While you should not call this function directly, you might want to know how exactly events are handled. So here is what this function does with the event:
- Compress enter/leave notify events. If the event passed build an enter/leave pair together with the next event (peeked from GDK), both events are thrown away. This is to avoid a backlog of (de-)highlighting widgets crossed by the pointer.
 - Find the widget which got the event. If the widget can’t be determined the event is thrown away unless it belongs to a INCR transaction.
 - Then the event is pushed onto a stack so you can query the currently
    handled event with 
getCurrentEvent. - The event is sent to a widget. If a grab is active all events for widgets
    that are not in the contained in the grab widget are sent to the latter
    with a few exceptions:
    - Deletion and destruction events are still sent to the event widget for
      obvious reasons.
    - Events which directly relate to the visual representation of the event
      widget.
    - Leave events are delivered to the event widget if there was an enter
      event delivered to it before without the paired leave event.
    - Drag events are not redirected because it is unclear what the semantics
      of that would be.
    Another point of interest might be that all key events are first passed
    through the key snooper functions if there are any. Read the description
    of 
gtk_key_snooper_install()if you need this feature. - After finishing the delivery the event is popped from the event stack.
 
mainIteration
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Bool | Returns:   | 
Runs a single iteration of the mainloop.
If no events are waiting to be processed GTK+ will block
 until the next event is noticed. If you don’t want to block
 look at mainIterationDo or check if any events are
 pending with eventsPending first.
mainIterationDo
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Bool | 
  | 
| -> m Bool | Returns:   | 
Runs a single iteration of the mainloop.
 If no events are available either return or block depending on
 the value of blocking.
mainLevel
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Word32 | Returns: the nesting level of the current invocation of the main loop  | 
Asks for the current nesting level of the main loop.
mainQuit
mainQuit :: (HasCallStack, MonadIO m) => m () Source #
Makes the innermost invocation of the main loop return when it regains control.
paintArrow
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> ArrowType | 
  | 
| -> Bool | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderArrow instead
Draws an arrow in the given rectangle on cr using the given
 parameters. arrowType determines the direction of the arrow.
paintBox
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderFrame and renderBackground instead
Draws a box on cr with the given parameters.
paintBoxGap
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> PositionType | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderFrameGap instead
Draws a box in cr using the given style and state and shadow type,
 leaving a gap in one side.
paintCheck
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderCheck instead
Draws a check button indicator in the given rectangle on cr with
 the given parameters.
paintDiamond
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use cairo instead
Draws a diamond in the given rectangle on window using the given
 parameters.
paintExpander
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> ExpanderStyle | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderExpander instead
Draws an expander as used in TreeView. x and y specify the
 center the expander. The size of the expander is determined by the
 “expander-size” style property of widget.  (If widget is not
 specified or doesn’t have an “expander-size” property, an
 unspecified default size will be used, since the caller doesn't
 have sufficient information to position the expander, this is
 likely not useful.) The expander is expander_size pixels tall
 in the collapsed position and expander_size pixels wide in the
 expanded position.
paintExtension
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> PositionType | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderExtension instead
Draws an extension, i.e. a notebook tab.
paintFlatBox
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderFrame and renderBackground instead
Draws a flat box on cr with the given parameters.
paintFocus
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderFocus instead
Draws a focus indicator around the given rectangle on cr using the
 given style.
paintHandle
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Orientation | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderHandle instead
paintHline
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderLine instead
Draws a horizontal line from (x1, y) to (x2, y) in cr
 using the given style and state.
paintLayout
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b, IsLayout c) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> Bool | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> c | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderLayout instead
Draws a layout on cr using the given parameters.
paintOption
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderOption instead
Draws a radio button indicator in the given rectangle on cr with
 the given parameters.
paintResizeGrip
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> WindowEdge | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderHandle instead
Draws a resize grip in the given rectangle on cr using the given
 parameters.
paintShadow
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderFrame instead
Draws a shadow around the given rectangle in cr
 using the given style and state and shadow type.
paintShadowGap
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> PositionType | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderFrameGap instead
Draws a shadow around the given rectangle in cr
 using the given style and state and shadow type, leaving a
 gap in one side.
paintSlider
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Orientation | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderSlider instead
Draws a slider in the given rectangle on cr using the
 given style and orientation.
paintSpinner
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Word32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderIcon and the StyleContext  you are drawing instead
Draws a spinner on window using the given parameters.
paintTab
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> ShadowType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use cairo instead
Draws an option menu tab (i.e. the up and down pointing arrows)
 in the given rectangle on cr using the given parameters.
paintVline
Arguments
| :: (HasCallStack, MonadIO m, IsStyle a, IsWidget b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> StateType | 
  | 
| -> Maybe b | 
  | 
| -> Maybe Text | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> Int32 | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use renderLine instead
Draws a vertical line from (x, y1_) to (x, y2_) in cr
 using the given style and state.
parseArgs
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [Text] | 
  | 
| -> m (Bool, [Text]) | Returns:   | 
Parses command line arguments, and initializes global
 attributes of GTK+, but does not actually open a connection
 to a display. (See displayOpen, getDisplayArgName)
Any arguments used by GTK+ or GDK are removed from the array and
 argc and argv are updated accordingly.
There is no need to call this function explicitly if you are using
 init, or initCheck.
Note that many aspects of GTK+ require a display connection to function, so this way of initializing GTK+ is really only useful for specialized use cases.
printRunPageSetupDialog
printRunPageSetupDialog Source #
Arguments
| :: (HasCallStack, MonadIO m, IsWindow a, IsPageSetup b, IsPrintSettings c) | |
| => Maybe a | 
  | 
| -> Maybe b | 
  | 
| -> c | 
  | 
| -> m PageSetup | Returns: a new   | 
Runs a page setup dialog, letting the user modify the values from
 pageSetup. If the user cancels the dialog, the returned PageSetup
 is identical to the passed in pageSetup, otherwise it contains the
 modifications done in the dialog.
Note that this function may use a recursive mainloop to show the page
 setup dialog. See printRunPageSetupDialogAsync if this is
 a problem.
Since: 2.10
printRunPageSetupDialogAsync
printRunPageSetupDialogAsync Source #
Arguments
| :: (HasCallStack, MonadIO m, IsWindow a, IsPageSetup b, IsPrintSettings c) | |
| => Maybe a | 
  | 
| -> Maybe b | |
| -> c | 
  | 
| -> PageSetupDoneFunc | 
  | 
| -> m () | 
Runs a page setup dialog, letting the user modify the values from pageSetup.
In contrast to printRunPageSetupDialog, this function  returns after
 showing the page setup dialog on platforms that support this, and calls doneCb
 from a signal handler for the response signal of the dialog.
Since: 2.10
propagateEvent
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Event | 
  | 
| -> m () | 
Sends an event to a widget, propagating the event to parent widgets if the event remains unhandled.
Events received by GTK+ from GDK normally begin in mainDoEvent.
 Depending on the type of event, existence of modal dialogs, grabs, etc.,
 the event may be propagated; if so, this function is used.
propagateEvent calls widgetEvent on each widget it
 decides to send the event to. So widgetEvent is the lowest-level
 function; it simply emits the event and possibly an
 event-specific signal on a widget. propagateEvent is a bit
 higher-level, and mainDoEvent is the highest level.
All that said, you most likely don’t want to use any of these
 functions; synthesizing events is rarely needed. There are almost
 certainly better ways to achieve your goals. For example, use
 windowInvalidateRect or widgetQueueDraw instead
 of making up expose events.
rcAddDefaultFile
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [Char] | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use StyleContext with a custom StyleProvider instead
Adds a file to the list of files to be parsed at the
 end of init.
rcFindModuleInPath
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
  | 
| -> m [Char] | Returns: The filename, if found (must be
   freed with   | 
Deprecated: (Since version 3.0)Use CssProvider instead.
Searches for a theme engine in the GTK+ search path. This function is not useful for applications and should not be used.
rcFindPixmapInPath
Arguments
| :: (HasCallStack, MonadIO m, IsSettings a) | |
| => a | 
  | 
| -> Scanner | 
  | 
| -> Text | 
  | 
| -> m [Char] | Returns: the filename.  | 
Deprecated: (Since version 3.0)Use CssProvider instead.
Looks up a file in pixmap path for the specified Settings.
 If the file is not found, it outputs a warning message using
 g_warning() and returns Nothing.
rcGetDefaultFiles
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m [[Char]] | Returns: 
      A   | 
Deprecated: (Since version 3.0)Use StyleContext instead
Retrieves the current list of RC files that will be parsed
 at the end of init.
rcGetImModuleFile
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m [Char] | Returns: a newly-allocated string containing the name of the file listing the IM modules available for loading  | 
Deprecated: (Since version 3.0)Use CssProvider instead.
Obtains the path to the IM modules file. See the documentation
 of the GTK_IM_MODULE_FILE
 environment variable for more details.
rcGetImModulePath
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m [Char] | Returns: a newly-allocated string containing the path in which to look for IM modules.  | 
Deprecated: (Since version 3.0)Use CssProvider instead.
Obtains the path in which to look for IM modules. See the documentation
 of the GTK_PATH
 environment variable for more details about looking up modules. This
 function is useful solely for utilities supplied with GTK+ and should
 not be used by applications under normal circumstances.
rcGetModuleDir
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m [Char] | Returns: the directory. (Must be freed with   | 
Deprecated: (Since version 3.0)Use CssProvider instead.
Returns a directory in which GTK+ looks for theme engines.
 For full information about the search for theme engines,
 see the docs for GTK_PATH in [Running GTK+ Applications][gtk-running].
rcGetStyle
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> m Style | Returns: the resulting style. No refcount is added to the returned style, so if you want to save this style around, you should add a reference yourself.  | 
Deprecated: (Since version 3.0)Use StyleContext instead
Finds all matching RC styles for a given widget,
 composites them together, and then creates a
 Style representing the composite appearance.
 (GTK+ actually keeps a cache of previously
 created styles, so a new style may not be
 created.)
rcGetStyleByPaths
Arguments
| :: (HasCallStack, MonadIO m, IsSettings a) | |
| => a | 
  | 
| -> Maybe Text | 
  | 
| -> Maybe Text | 
  | 
| -> GType | 
  | 
| -> m (Maybe Style) | Returns: A style created by matching
     with the supplied paths, or   | 
Deprecated: (Since version 3.0)Use StyleContext instead
Creates up a Style from styles defined in a RC file by providing
 the raw components used in matching. This function may be useful
 when creating pseudo-widgets that should be themed like widgets but
 don’t actually have corresponding GTK+ widgets. An example of this
 would be items inside a GNOME canvas widget.
The action of rcGetStyle is similar to:
C code
gtk_widget_path (widget, NULL, &path, NULL);
gtk_widget_class_path (widget, NULL, &class_path, NULL);
gtk_rc_get_style_by_paths (gtk_widget_get_settings (widget),
                           path, class_path,
                           G_OBJECT_TYPE (widget));rcGetThemeDir
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Text | Returns: The directory (must be freed with   | 
Deprecated: (Since version 3.0)Use CssProvider instead.
Returns the standard directory in which themes should be installed. (GTK+ does not actually use this directory itself.)
rcParse
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use CssProvider instead.
Parses a given resource file.
rcParseColor
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Scanner | 
  | 
| -> m (Word32, Color) | Returns:   | 
Deprecated: (Since version 3.0)Use CssProvider instead
Parses a color in the format expected in a RC file.
Note that theme engines should use rcParseColorFull in
 order to support symbolic colors.
rcParseColorFull
Arguments
| :: (HasCallStack, MonadIO m, IsRcStyle a) | |
| => Scanner | 
  | 
| -> Maybe a | |
| -> m (Word32, Color) | Returns:   | 
Deprecated: (Since version 3.0)Use CssProvider instead
Parses a color in the format expected
 in a RC file. If style is not Nothing, it will be consulted to resolve
 references to symbolic colors.
Since: 2.12
rcParsePriority
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Scanner | 
  | 
| -> PathPriorityType | 
  | 
| -> m Word32 | Returns:   | 
Deprecated: (Since version 3.0)Use CssProvider instead
Parses a PathPriorityType variable from the format expected
 in a RC file.
rcParseState
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Scanner | 
  | 
| -> m (Word32, StateType) | Returns:   | 
Deprecated: (Since version 3.0)Use CssProvider instead
Parses a StateType variable from the format expected
 in a RC file.
rcParseString
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use CssProvider instead.
Parses resource information directly from a string.
rcReparseAll
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Bool | Returns:   | 
Deprecated: (Since version 3.0)Use CssProvider instead.
If the modification time on any previously read file for the
 default Settings has changed, discard all style information
 and then reread all previously read RC files.
rcReparseAllForSettings
rcReparseAllForSettings Source #
Arguments
| :: (HasCallStack, MonadIO m, IsSettings a) | |
| => a | 
  | 
| -> Bool | 
  | 
| -> m Bool | Returns:   | 
Deprecated: (Since version 3.0)Use CssProvider instead.
If the modification time on any previously read file
 for the given Settings has changed, discard all style information
 and then reread all previously read RC files.
rcResetStyles
Arguments
| :: (HasCallStack, MonadIO m, IsSettings a) | |
| => a | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use CssProvider instead.
This function recomputes the styles for all widgets that use a
 particular Settings object. (There is one Settings object
 per Screen, see settingsGetForScreen); It is useful
 when some global parameter has changed that affects the appearance
 of all widgets, because when a widget gets a new style, it will
 both redraw and recompute any cached information about its
 appearance. As an example, it is used when the default font size
 set by the operating system changes. Note that this function
 doesn’t affect widgets that have a style set explicitly on them
 with widgetSetStyle.
Since: 2.4
rcSetDefaultFiles
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [[Char]] | 
  | 
| -> m () | 
Deprecated: (Since version 3.0)Use StyleContext with a custom StyleProvider instead
Sets the list of files that GTK+ will read at the
 end of init.
renderActivity
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders an activity indicator (such as in Spinner).
 The state StateFlagsChecked determines whether there is
 activity going on.
Since: 3.0
renderArrow
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders an arrow pointing to angle.
Typical arrow rendering at 0, 1⁄2 π;, π; and 3⁄2 π:

Since: 3.0
renderBackground
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders the background of an element.
Typical background rendering, showing the effect of
 background-image, border-width and border-radius:

Since: 3.0.
renderBackgroundGetClip
renderBackgroundGetClip Source #
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m Rectangle | 
Returns the area that will be affected (i.e. drawn to) when
 calling renderBackground for the given context and
 rectangle.
Since: 3.20
renderCheck
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders a checkmark (as in a CheckButton).
The StateFlagsChecked state determines whether the check is
 on or off, and StateFlagsInconsistent determines whether it
 should be marked as undefined.
Typical checkmark rendering:

Since: 3.0
renderExpander
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders an expander (as used in TreeView and Expander) in the area
 defined by x, y, width, height. The state StateFlagsChecked
 determines whether the expander is collapsed or expanded.
Typical expander rendering:

Since: 3.0
renderExtension
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> PositionType | 
  | 
| -> m () | 
Renders a extension (as in a Notebook tab) in the rectangle
 defined by x, y, width, height. The side where the extension
 connects to is defined by gapSide.
Typical extension rendering:

Since: 3.0
renderFocus
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders a focus indicator on the rectangle determined by x, y, width, height.
Typical focus rendering:

Since: 3.0
renderFrame
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders a frame around the rectangle defined by x, y, width, height.
Examples of frame rendering, showing the effect of border-image,
 border-color, border-width, border-radius and junctions:

Since: 3.0
renderFrameGap
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> PositionType | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Deprecated: (Since version 3.24)Use renderFrame instead. Themes can create gaps    by omitting borders via CSS.
Renders a frame around the rectangle defined by (x, y, width, height),
 leaving a gap on one side. xy0Gap and xy1Gap will mean X coordinates
 for PositionTypeTop and PositionTypeBottom gap sides, and Y coordinates for
 PositionTypeLeft and PositionTypeRight.
Typical rendering of a frame with a gap:

Since: 3.0
renderHandle
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
renderIcon
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a, IsPixbuf b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> b | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders the icon in pixbuf at the specified x and y coordinates.
This function will render the icon in pixbuf at exactly its size,
 regardless of scaling factors, which may not be appropriate when
 drawing on displays with high pixel densities.
You probably want to use renderIconSurface instead, if you
 already have a Cairo surface.
Since: 3.2
renderIconPixbuf
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> IconSource | 
  | 
| -> Int32 | 
  | 
| -> m Pixbuf | Returns: a newly-created   | 
Deprecated: (Since version 3.10)Use iconThemeLoadIcon instead.
Renders the icon specified by source at the given size, returning the result
 in a pixbuf.
Since: 3.0
renderIconSurface
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Surface | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders the icon in surface at the specified x and y coordinates.
Since: 3.10
renderInsertionCursor
renderInsertionCursor Source #
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a, IsLayout b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> b | 
  | 
| -> Int32 | 
  | 
| -> Direction | 
  | 
| -> m () | 
Draws a text caret on cr at the specified index of layout.
Since: 3.4
renderLayout
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a, IsLayout b) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> b | 
  | 
| -> m () | 
Renders layout on the coordinates x, y
Since: 3.0
renderLine
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders a line from (x0, y0) to (x1, y1).
Since: 3.0
renderOption
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m () | 
Renders an option mark (as in a RadioButton), the StateFlagsChecked
 state will determine whether the option is on or off, and
 StateFlagsInconsistent whether it should be marked as undefined.
Typical option mark rendering:

Since: 3.0
renderSlider
Arguments
| :: (HasCallStack, MonadIO m, IsStyleContext a) | |
| => a | 
  | 
| -> Context | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> Orientation | 
  | 
| -> m () | 
Renders a slider (as in Scale) in the rectangle defined by x, y,
 width, height. orientation defines whether the slider is vertical
 or horizontal.
Typical slider rendering:

Since: 3.0
rgbToHsv
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Double | 
  | 
| -> Double | 
  | 
| -> Double | 
  | 
| -> m (Double, Double, Double) | 
Converts a color from RGB space to HSV.
Input values must be in the [0.0, 1.0] range; output values will be in the same range.
Since: 2.14
selectionAddTarget
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Atom | 
  | 
| -> Atom | 
  | 
| -> Word32 | 
  | 
| -> m () | 
Appends a specified target to the list of supported targets for a given widget and selection.
selectionAddTargets
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Atom | 
  | 
| -> [TargetEntry] | 
  | 
| -> m () | 
Prepends a table of targets to the list of supported targets for a given widget and selection.
selectionClearTargets
selectionClearTargets Source #
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Atom | 
  | 
| -> m () | 
Remove all targets registered for the given selection for the widget.
selectionConvert
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Atom | 
  | 
| -> Atom | 
  | 
| -> Word32 | 
  | 
| -> m Bool | Returns:   | 
Requests the contents of a selection. When received, a “selection-received” signal will be generated.
selectionOwnerSet
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => Maybe a | |
| -> Atom | 
  | 
| -> Word32 | 
  | 
| -> m Bool | Returns:   | 
Claims ownership of a given selection for a particular widget,
 or, if widget is Nothing, release ownership of the selection.
selectionOwnerSetForDisplay
selectionOwnerSetForDisplay Source #
Arguments
| :: (HasCallStack, MonadIO m, IsDisplay a, IsWidget b) | |
| => a | 
  | 
| -> Maybe b | |
| -> Atom | 
  | 
| -> Word32 | 
  | 
| -> m Bool | Returns: TRUE if the operation succeeded  | 
Claim ownership of a given selection for a particular widget, or,
 if widget is Nothing, release ownership of the selection.
Since: 2.2
selectionRemoveAll
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> m () | 
Removes all handlers and unsets ownership of all selections for a widget. Called when widget is being destroyed. This function will not generally be called by applications.
setDebugFlags
setDebugFlags :: (HasCallStack, MonadIO m) => Word32 -> m () Source #
Sets the GTK+ debug flags.
showUri
Arguments
| :: (HasCallStack, MonadIO m, IsScreen a) | |
| => Maybe a | 
  | 
| -> Text | 
  | 
| -> Word32 | 
  | 
| -> m () | (Can throw   | 
A convenience function for launching the default application
 to show the uri. Like showUriOnWindow, but takes a screen
 as transient parent instead of a window.
Note that this function is deprecated as it does not pass the necessary information for helpers to parent their dialog properly, when run from sandboxed applications for example.
Since: 2.14
showUriOnWindow
Arguments
| :: (HasCallStack, MonadIO m, IsWindow a) | |
| => Maybe a | 
  | 
| -> Text | 
  | 
| -> Word32 | 
  | 
| -> m () | (Can throw   | 
This is a convenience function for launching the default application to show the uri. The uri must be of a form understood by GIO (i.e. you need to install gvfs to get support for uri schemes such as http:// or ftp://, as only local files are handled by GIO itself). Typical examples are
file:///home/gnome/pict.jpg
http://www.gnome.org
mailto:me@gnome.org
Ideally the timestamp is taken from the event triggering
 the showUri call. If timestamp is not known you can take
 CURRENT_TIME.
This is the recommended call to be used as it passes information necessary for sandbox helpers to parent their dialogs properly.
Since: 3.22
stockAdd
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [StockItem] | 
  | 
| -> m () | 
Deprecated: (Since version 3.10)
Registers each of the stock items in items. If an item already
 exists with the same stock ID as one of the items, the old item
 gets replaced. The stock items are copied, so GTK+ does not hold
 any pointer into items and items can be freed. Use
 stockAddStatic if items is persistent and GTK+ need not
 copy the array.
stockAddStatic
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [StockItem] | |
| -> m () | 
Deprecated: (Since version 3.10)
Same as stockAdd, but doesn’t copy items, so
 items must persist until application exit.
stockListIds
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m [Text] | Returns: a list of known stock IDs  | 
Deprecated: (Since version 3.10)
Retrieves a list of all known stock IDs added to a IconFactory
 or registered with stockAdd. The list must be freed with g_slist_free(),
 and each string in the list must be freed with free.
stockLookup
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
  | 
| -> m (Bool, StockItem) | Returns:   | 
Deprecated: (Since version 3.10)
Fills item with the registered values for stockId, returning True
 if stockId was known.
stockSetTranslateFunc
stockSetTranslateFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
  | 
| -> TranslateFunc | 
  | 
| -> m () | 
Deprecated: (Since version 3.10)
Sets a function to be used for translating the label of
 a stock item.
If no function is registered for a translation domain,
 dgettext is used.
The function is used for all stock items whose
 translationDomain matches domain. Note that it is possible
 to use strings different from the actual gettext translation domain
 of your application for this, as long as your TranslateFunc uses
 the correct domain when calling dgettext(). This can be useful, e.g.
 when dealing with message contexts:
C code
GtkStockItem items[] = {
 { MY_ITEM1, NC_("odd items", "Item 1"), 0, 0, "odd-item-domain" },
 { MY_ITEM2, NC_("even items", "Item 2"), 0, 0, "even-item-domain" },
};
gchar *
my_translate_func (const gchar *msgid,
                   gpointer     data)
{
  gchar *msgctxt = data;
  return (gchar*)g_dpgettext2 (GETTEXT_PACKAGE, msgctxt, msgid);
}
...
gtk_stock_add (items, G_N_ELEMENTS (items));
gtk_stock_set_translate_func ("odd-item-domain", my_translate_func, "odd items");
gtk_stock_set_translate_func ("even-item-domain", my_translate_func, "even items");Since: 2.8
targetTableFree
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [TargetEntry] | 
  | 
| -> m () | 
This function frees a target table as returned by
 targetTableNewFromList
Since: 2.10
targetTableNewFromList
targetTableNewFromList Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => TargetList | 
  | 
| -> m [TargetEntry] | Returns: the new table.  | 
This function creates an TargetEntry array that contains the
 same targets as the passed list. The returned table is newly
 allocated and should be freed using targetTableFree when no
 longer needed.
Since: 2.10
targetsIncludeImage
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [Atom] | 
  | 
| -> Bool | 
  | 
| -> m Bool | Returns:   | 
Determines if any of the targets in targets can be used to
 provide a Pixbuf.
Since: 2.10
targetsIncludeRichText
targetsIncludeRichText Source #
Arguments
| :: (HasCallStack, MonadIO m, IsTextBuffer a) | |
| => [Atom] | 
  | 
| -> a | 
  | 
| -> m Bool | Returns:   | 
Determines if any of the targets in targets can be used to
 provide rich text.
Since: 2.10
targetsIncludeText
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [Atom] | 
  | 
| -> m Bool | Returns:   | 
Determines if any of the targets in targets can be used to
 provide text.
Since: 2.10
targetsIncludeUri
Arguments
| :: (HasCallStack, MonadIO m) | |
| => [Atom] | 
  | 
| -> m Bool | Returns:   | 
Determines if any of the targets in targets can be used to
 provide an uri list.
Since: 2.10
testCreateSimpleWindow
testCreateSimpleWindow Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => Text | 
  | 
| -> Text | 
  | 
| -> m Widget | Returns: a widget pointer to the newly created GtkWindow.  | 
Deprecated: (Since version 3.20)This testing infrastructure is phased out in favor of reftests.
Create a simple window with window title windowTitle and
 text contents dialogText.
 The window will quit any running main-loop when destroyed, and it
 will automatically be destroyed upon test function teardown.
Since: 2.14
testFindLabel
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Text | 
  | 
| -> m Widget | Returns: a GtkLabel widget if any is found.  | 
This function will search widget and all its descendants for a GtkLabel
 widget with a text string matching labelPattern.
 The labelPattern may contain asterisks “*” and question marks “?” as
 placeholders, patternMatch is used for the matching.
 Note that locales other than "C“ tend to alter (translate” label strings,
 so this function is genrally only useful in test programs with
 predetermined locales, see gtk_test_init() for more details.
Since: 2.14
testFindSibling
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> GType | 
  | 
| -> m Widget | Returns: a widget of type   | 
This function will search siblings of baseWidget and siblings of its
 ancestors for all widgets matching widgetType.
 Of the matching widgets, the one that is geometrically closest to
 baseWidget will be returned.
 The general purpose of this function is to find the most likely “action”
 widget, relative to another labeling widget. Such as finding a
 button or text entry widget, given its corresponding label widget.
Since: 2.14
testFindWidget
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Text | 
  | 
| -> GType | 
  | 
| -> m (Maybe Widget) | Returns: a valid widget if any is found or   | 
This function will search the descendants of widget for a widget
 of type widgetType that has a label matching labelPattern next
 to it. This is most useful for automated GUI testing, e.g. to find
 the “OK” button in a dialog and synthesize clicks on it.
 However see testFindLabel, testFindSibling and
 testWidgetClick for possible caveats involving the search of
 such widgets and synthesizing widget events.
Since: 2.14
testListAllTypes
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m ([GType], Word32) | Returns: 0-terminated array of type ids  | 
Return the type ids that have been registered after
 calling testRegisterAllTypes.
Since: 2.14
testRegisterAllTypes
testRegisterAllTypes :: (HasCallStack, MonadIO m) => m () Source #
Force registration of all core Gtk+ and Gdk object types.
 This allowes to refer to any of those object types via
 typeFromName after calling this function.
Since: 2.14
testSliderGetValue
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> m Double | Returns: gtk_adjustment_get_value (adjustment) for an adjustment belonging to   | 
Deprecated: (Since version 3.20)This testing infrastructure is phased out in favor of reftests.
Retrive the literal adjustment value for GtkRange based
 widgets and spin buttons. Note that the value returned by
 this function is anything between the lower and upper bounds
 of the adjustment belonging to widget, and is not a percentage
 as passed in to testSliderSetPerc.
Since: 2.14
testSliderSetPerc
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Double | 
  | 
| -> m () | 
Deprecated: (Since version 3.20)This testing infrastructure is phased out in favor of reftests.
This function will adjust the slider position of all GtkRange
 based widgets, such as scrollbars or scales, it’ll also adjust
 spin buttons. The adjustment value of these widgets is set to
 a value between the lower and upper limits, according to the
 percentage argument.
Since: 2.14
testSpinButtonClick
Arguments
| :: (HasCallStack, MonadIO m, IsSpinButton a) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> Bool | 
  | 
| -> m Bool | Returns: whether all actions neccessary for the button click simulation were carried out successfully.  | 
Deprecated: (Since version 3.20)This testing infrastructure is phased out in favor of reftests.
This function will generate a button click in the upwards or downwards
 spin button arrow areas, usually leading to an increase or decrease of
 spin button’s value.
Since: 2.14
testTextGet
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> m Text | Returns: new 0-terminated C string, needs to be released with   | 
Deprecated: (Since version 3.20)This testing infrastructure is phased out in favor of reftests.
Retrive the text string of widget if it is a GtkLabel,
 GtkEditable (entry and text widgets) or GtkTextView.
Since: 2.14
testTextSet
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Text | 
  | 
| -> m () | 
Deprecated: (Since version 3.20)This testing infrastructure is phased out in favor of reftests.
Set the text string of widget to string if it is a GtkLabel,
 GtkEditable (entry and text widgets) or GtkTextView.
Since: 2.14
testWidgetClick
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Bool | Returns: whether all actions neccessary for the button click simulation were carried out successfully.  | 
Deprecated: (Since version 3.20)This testing infrastructure is phased out in favor of reftests.
This function will generate a button click (button press and button
 release event) in the middle of the first GdkWindow found that belongs
 to widget.
 For windowless widgets like Button (which returns False from
 widgetGetHasWindow), this will often be an
 input-only event window. For other widgets, this is usually widget->window.
 Certain caveats should be considered when using this function, in
 particular because the mouse pointer is warped to the button click
 location, see testSimulateButton for details.
Since: 2.14
testWidgetSendKey
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Bool | Returns: whether all actions neccessary for the key event simulation were carried out successfully.  | 
This function will generate keyboard press and release events in
 the middle of the first GdkWindow found that belongs to widget.
 For windowless widgets like Button (which returns False from
 widgetGetHasWindow), this will often be an
 input-only event window. For other widgets, this is usually widget->window.
 Certain caveats should be considered when using this function, in
 particular because the mouse pointer is warped to the key press
 location, see testSimulateKey for details.
Since: 2.14
testWidgetWaitForDraw
testWidgetWaitForDraw Source #
Arguments
| :: (HasCallStack, MonadIO m, IsWidget a) | |
| => a | 
  | 
| -> m () | 
Enters the main loop and waits for widget to be “drawn”. In this
 context that means it waits for the frame clock of widget to have
 run a full styling, layout and drawing cycle.
This function is intended to be used for syncing with actions that
 depend on widget relayouting or on interaction with the display
 server.
Since: 3.10
treeGetRowDragData
Arguments
| :: (HasCallStack, MonadIO m) | |
| => SelectionData | 
  | 
| -> m (Bool, Maybe TreeModel, Maybe TreePath) | Returns:   | 
Obtains a treeModel and path from selection data of target type
 GTK_TREE_MODEL_ROW. Normally called from a drag_data_received handler.
 This function can only be used if selectionData originates from the same
 process that’s calling this function, because a pointer to the tree model
 is being passed around. If you aren’t in the same process, then you'll
 get memory corruption. In the TreeDragDest drag_data_received handler,
 you can assume that selection data of type GTK_TREE_MODEL_ROW is
 in from the current process. The returned path must be freed with
 treePathFree.
treeSetRowDragData
Arguments
| :: (HasCallStack, MonadIO m, IsTreeModel a) | |
| => SelectionData | 
  | 
| -> a | 
  | 
| -> TreePath | 
  | 
| -> m Bool | Returns:   | 
Sets selection data of target type GTK_TREE_MODEL_ROW. Normally used
 in a drag_data_get handler.
true
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m Bool | Returns:   | 
All this function does it to return True.
This can be useful for example if you want to inhibit the deletion of a window. Of course you should not do this as the user expects a reaction from clicking the close icon of the window...
A persistent window
C code
#include <gtk/gtk.h>
int
main (int argc, char **argv)
{
  GtkWidget *win, *but;
  const char *text = "Close yourself. I mean it!";
  gtk_init (&argc, &argv);
  win = gtk_window_new (GTK_WINDOW_TOPLEVEL);
  g_signal_connect (win,
                    "delete-event",
                    G_CALLBACK (gtk_true),
                    NULL);
  g_signal_connect (win, "destroy",
                    G_CALLBACK (gtk_main_quit),
                    NULL);
  but = gtk_button_new_with_label (text);
  g_signal_connect_swapped (but, "clicked",
                            G_CALLBACK (gtk_object_destroy),
                            win);
  gtk_container_add (GTK_CONTAINER (win), but);
  gtk_widget_show_all (win);
  gtk_main ();
  return 0;
}