Gtk2HsContentsIndex
Graphics.UI.Gtk.Mogul.NewWidget
Description

These functions generate a new widget with a name.

  • The widget can later be lookup up by its name from the global store. As soon as the widget is destroyed it is deleted from the store. If a given name is still available can be tested by the isValidName function.
Synopsis
newTextBuffer :: Maybe TextTagTable -> IO TextBuffer
newLabel :: Maybe String -> IO Label
newNamedLabel :: WidgetName -> Maybe String -> IO Label
newAccelLabel :: String -> IO AccelLabel
newNamedAccelLabel :: WidgetName -> String -> IO AccelLabel
newArrow :: ArrowType -> ShadowType -> IO Arrow
newNamedArrow :: WidgetName -> ArrowType -> ShadowType -> IO Arrow
newImageFromFile :: FilePath -> IO Image
newNamedImageFromFile :: WidgetName -> FilePath -> IO Image
newAlignment :: Float -> Float -> Float -> Float -> IO Alignment
newNamedAlignment :: WidgetName -> Float -> Float -> Float -> Float -> IO Alignment
newFrame :: IO Frame
newNamedFrame :: WidgetName -> IO Frame
newAspectFrame :: Float -> Float -> Maybe Float -> IO AspectFrame
newNamedAspectFrame :: WidgetName -> Float -> Float -> Maybe Float -> IO AspectFrame
newButton :: IO Button
newNamedButton :: WidgetName -> IO Button
newButtonWithLabel :: String -> IO Button
newNamedButtonWithLabel :: WidgetName -> String -> IO Button
newButtonWithMnemonic :: String -> IO Button
newNamedButtonWithMnemonic :: WidgetName -> String -> IO Button
newButtonFromStock :: String -> IO Button
newNamedButtonFromStock :: WidgetName -> String -> IO Button
newToggleButton :: IO ToggleButton
newNamedToggleButton :: WidgetName -> IO ToggleButton
newToggleButtonWithLabel :: String -> IO ToggleButton
newNamedToggleButtonWithLabel :: WidgetName -> String -> IO ToggleButton
newCheckButton :: IO CheckButton
newNamedCheckButton :: WidgetName -> IO CheckButton
newCheckButtonWithLabel :: String -> IO CheckButton
newNamedCheckButtonWithLabel :: WidgetName -> String -> IO CheckButton
newCheckButtonWithMnemonic :: String -> IO CheckButton
newNamedCheckButtonWithMnemonic :: WidgetName -> String -> IO CheckButton
newRadioButton :: IO RadioButton
newNamedRadioButton :: WidgetName -> IO RadioButton
newRadioButtonWithLabel :: String -> IO RadioButton
newNamedRadioButtonWithLabel :: WidgetName -> String -> IO RadioButton
newRadioButtonJoinGroup :: RadioButton -> IO RadioButton
newNamedRadioButtonJoinGroup :: WidgetName -> RadioButton -> IO RadioButton
newRadioButtonJoinGroupWithLabel :: RadioButton -> String -> IO RadioButton
newNamedRadioButtonJoinGroupWithLabel :: WidgetName -> RadioButton -> String -> IO RadioButton
newOptionMenu :: IO OptionMenu
newNamedOptionMenu :: WidgetName -> IO OptionMenu
newMenuItem :: IO MenuItem
newNamedMenuItem :: WidgetName -> IO MenuItem
newMenuItemWithLabel :: String -> IO MenuItem
newNamedMenuItemWithLabel :: WidgetName -> String -> IO MenuItem
newCheckMenuItem :: IO CheckMenuItem
newNamedCheckMenuItem :: WidgetName -> IO CheckMenuItem
newCheckMenuItemWithLabel :: String -> IO CheckMenuItem
newNamedCheckMenuItemWithLabel :: WidgetName -> String -> IO CheckMenuItem
newRadioMenuItem :: IO RadioMenuItem
newNamedRadioMenuItem :: WidgetName -> IO RadioMenuItem
newRadioMenuItemWithLabel :: String -> IO RadioMenuItem
newNamedRadioMenuItemWithLabel :: WidgetName -> String -> IO RadioMenuItem
newRadioMenuItemJoinGroup :: RadioMenuItem -> IO RadioMenuItem
newNamedRadioMenuItemJoinGroup :: WidgetName -> RadioMenuItem -> IO RadioMenuItem
newRadioMenuItemJoinGroupWithLabel :: RadioMenuItem -> String -> IO RadioMenuItem
newNamedRadioMenuItemJoinGroupWithLabel :: WidgetName -> RadioMenuItem -> String -> IO RadioMenuItem
newTearoffMenuItem :: IO TearoffMenuItem
newNamedTearoffMenuItem :: WidgetName -> IO TearoffMenuItem
newWindow :: IO Window
newNamedWindow :: WidgetName -> IO Window
newDialog :: IO Dialog
newNamedDialog :: WidgetName -> IO Dialog
newEventBox :: IO EventBox
newNamedEventBox :: WidgetName -> IO EventBox
newHandleBox :: IO HandleBox
newNamedHandleBox :: WidgetName -> IO HandleBox
newScrolledWindow :: Maybe Adjustment -> Maybe Adjustment -> IO ScrolledWindow
newNamedScrolledWindow :: WidgetName -> Maybe Adjustment -> Maybe Adjustment -> IO ScrolledWindow
newViewport :: Adjustment -> Adjustment -> IO Viewport
newNamedViewport :: WidgetName -> Adjustment -> Adjustment -> IO Viewport
newVBox :: Bool -> Int -> IO VBox
newNamedVBox :: WidgetName -> Bool -> Int -> IO VBox
newHBox :: Bool -> Int -> IO HBox
newNamedHBox :: WidgetName -> Bool -> Int -> IO HBox
newCombo :: IO Combo
newNamedCombo :: WidgetName -> IO Combo
newStatusbar :: IO Statusbar
newNamedStatusbar :: WidgetName -> IO Statusbar
newHPaned :: IO HPaned
newNamedHPaned :: WidgetName -> IO HPaned
newVPaned :: IO VPaned
newNamedVPaned :: WidgetName -> IO VPaned
newLayout :: Maybe Adjustment -> Maybe Adjustment -> IO Layout
newNamedLayout :: WidgetName -> Maybe Adjustment -> Maybe Adjustment -> IO Layout
newMenu :: IO Menu
newNamedMenu :: WidgetName -> IO Menu
newMenuBar :: IO MenuBar
newNamedMenuBar :: WidgetName -> IO MenuBar
newNotebook :: IO Notebook
newNamedNotebook :: WidgetName -> IO Notebook
newTable :: Int -> Int -> Bool -> IO Table
newNamedTable :: WidgetName -> Int -> Int -> Bool -> IO Table
newTextView :: IO TextView
newNamedTextView :: WidgetName -> IO TextView
newToolbar :: IO Toolbar
newNamedToolbar :: WidgetName -> IO Toolbar
newCalendar :: IO Calendar
newNamedCalendar :: WidgetName -> IO Calendar
newEntry :: IO Entry
newNamedEntry :: WidgetName -> IO Entry
newSpinButton :: Adjustment -> Double -> Int -> IO SpinButton
newNamedSpinButton :: String -> Adjustment -> Double -> Int -> IO SpinButton
newSpinButtonWithRange :: Double -> Double -> Double -> IO SpinButton
newNamedSpinButtonWithRange :: WidgetName -> Double -> Double -> Double -> IO SpinButton
newHScale :: Adjustment -> IO HScale
newNamedHScale :: WidgetName -> Adjustment -> IO HScale
newVScale :: Adjustment -> IO VScale
newNamedVScale :: WidgetName -> Adjustment -> IO VScale
newHScrollbar :: Adjustment -> IO HScrollbar
newNamedHScrollbar :: WidgetName -> Adjustment -> IO HScrollbar
newVScrollbar :: Adjustment -> IO VScrollbar
newNamedVScrollbar :: WidgetName -> Adjustment -> IO VScrollbar
newHSeparator :: IO HSeparator
newNamedHSeparator :: WidgetName -> IO HSeparator
newVSeparator :: IO VSeparator
newNamedVSeparator :: WidgetName -> IO VSeparator
newProgressBar :: IO ProgressBar
newNamedProgressBar :: WidgetName -> IO ProgressBar
newAdjustment :: Double -> Double -> Double -> Double -> Double -> Double -> IO Adjustment
newTooltips :: IO Tooltips
newTreeView :: TreeModelClass tm => tm -> IO TreeView
newNamedTreeView :: TreeModelClass tm => WidgetName -> tm -> IO TreeView
newTreeViewWithModel :: TreeModelClass tm => tm -> IO TreeView
newNamedTreeViewWithModel :: TreeModelClass tm => WidgetName -> tm -> IO TreeView
newTreeViewColumn :: IO TreeViewColumn
newIconFactory :: IO IconFactory
Documentation
newTextBuffer :: Maybe TextTagTable -> IO TextBuffer
see textBufferNew
newLabel :: Maybe String -> IO Label
see labelNew
newNamedLabel :: WidgetName -> Maybe String -> IO Label

see textTagNew

newTextTag :: IO TextTag newTextTag = textTagNew

see textTagTableNew

newTextTagTable :: IO TextTagTable newTextTagTable = textTagTableNew

see labelNew

  • The supplied name can later be used to lookup the widget in the global store.
newAccelLabel :: String -> IO AccelLabel
see accelLabelNew
newNamedAccelLabel :: WidgetName -> String -> IO AccelLabel

see accelLabelNew

  • The supplied name can later be used to lookup the widget in the global store.
newArrow :: ArrowType -> ShadowType -> IO Arrow
see arrowNew
newNamedArrow :: WidgetName -> ArrowType -> ShadowType -> IO Arrow

see arrowNew

  • The supplied name can later be used to lookup the widget in the global store.
newImageFromFile :: FilePath -> IO Image
see imageNewFromFile
newNamedImageFromFile :: WidgetName -> FilePath -> IO Image

see imageNewFromFile

  • The supplied name can later be used to lookup the widget in the global store.
newAlignment :: Float -> Float -> Float -> Float -> IO Alignment
see alignmentNew
newNamedAlignment :: WidgetName -> Float -> Float -> Float -> Float -> IO Alignment

see alignmentNew

  • The supplied name can later be used to lookup the widget in the global store.
newFrame :: IO Frame
see frameNew
newNamedFrame :: WidgetName -> IO Frame

see frameNew

  • The supplied name can later be used to lookup the widget in the global store.
newAspectFrame :: Float -> Float -> Maybe Float -> IO AspectFrame
see aspectFrameNew
newNamedAspectFrame :: WidgetName -> Float -> Float -> Maybe Float -> IO AspectFrame

see aspectFrameNew

  • The supplied name can later be used to lookup the widget in the global store.
newButton :: IO Button
see buttonNew
newNamedButton :: WidgetName -> IO Button

see buttonNew

  • The supplied name can later be used to lookup the widget in the global store.
newButtonWithLabel :: String -> IO Button
see buttonNewWithLabel
newNamedButtonWithLabel :: WidgetName -> String -> IO Button

see buttonNewWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newButtonWithMnemonic :: String -> IO Button
see buttonNewWithMnemonic
newNamedButtonWithMnemonic :: WidgetName -> String -> IO Button

see buttonNewWithMnemonic

  • The supplied name can later be used to lookup the widget in the global store.
newButtonFromStock :: String -> IO Button
see buttonNewFromStock
newNamedButtonFromStock :: WidgetName -> String -> IO Button

see buttonNewFromStock

  • The supplied name can later be used to lookup the widget in the global store.
newToggleButton :: IO ToggleButton
see toggleButtonNew
newNamedToggleButton :: WidgetName -> IO ToggleButton

see toggleButtonNew

  • The supplied name can later be used to lookup the widget in the global store.
newToggleButtonWithLabel :: String -> IO ToggleButton
see toggleButtonNewWithLabel
newNamedToggleButtonWithLabel :: WidgetName -> String -> IO ToggleButton

see toggleButtonNewWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newCheckButton :: IO CheckButton
see checkButtonNew
newNamedCheckButton :: WidgetName -> IO CheckButton

see checkButtonNew

  • The supplied name can later be used to lookup the widget in the global store.
newCheckButtonWithLabel :: String -> IO CheckButton
see checkButtonNewWithLabel
newNamedCheckButtonWithLabel :: WidgetName -> String -> IO CheckButton

see checkButtonNewWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newCheckButtonWithMnemonic :: String -> IO CheckButton
see checkButtonNewWithMnemonic
newNamedCheckButtonWithMnemonic :: WidgetName -> String -> IO CheckButton

see checkButtonNewWithMnemonic

  • The supplied name can later be used to lookup the widget in the global store.
newRadioButton :: IO RadioButton
see radioButtonNew
newNamedRadioButton :: WidgetName -> IO RadioButton

see radioButtonNew

  • The supplied name can later be used to lookup the widget in the global store.
newRadioButtonWithLabel :: String -> IO RadioButton
see radioButtonNewWithLabel
newNamedRadioButtonWithLabel :: WidgetName -> String -> IO RadioButton

see radioButtonNewWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newRadioButtonJoinGroup :: RadioButton -> IO RadioButton
see radioButtonNewJoinGroup
newNamedRadioButtonJoinGroup :: WidgetName -> RadioButton -> IO RadioButton

see radioButtonNewJoinGroup

  • The supplied name can later be used to lookup the widget in the global store.
newRadioButtonJoinGroupWithLabel :: RadioButton -> String -> IO RadioButton
see radioButtonNewJoinGroupWithLabel
newNamedRadioButtonJoinGroupWithLabel :: WidgetName -> RadioButton -> String -> IO RadioButton

see radioButtonNewJoinGroupWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newOptionMenu :: IO OptionMenu
see optionMenuNew
newNamedOptionMenu :: WidgetName -> IO OptionMenu

see optionMenuNew

  • The supplied name can later be used to lookup the widget in the global store.
newMenuItem :: IO MenuItem
see menuItemNew
newNamedMenuItem :: WidgetName -> IO MenuItem

see menuItemNew

  • The supplied name can later be used to lookup the widget in the global store.
newMenuItemWithLabel :: String -> IO MenuItem
see menuItemNewWithLabel
newNamedMenuItemWithLabel :: WidgetName -> String -> IO MenuItem

see menuItemNewWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newCheckMenuItem :: IO CheckMenuItem
see checkMenuItemNew
newNamedCheckMenuItem :: WidgetName -> IO CheckMenuItem

see checkMenuItemNew

  • The supplied name can later be used to lookup the widget in the global store.
newCheckMenuItemWithLabel :: String -> IO CheckMenuItem
see checkMenuItemNewWithLabel
newNamedCheckMenuItemWithLabel :: WidgetName -> String -> IO CheckMenuItem

see checkMenuItemNewWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newRadioMenuItem :: IO RadioMenuItem
see radioMenuItemNew
newNamedRadioMenuItem :: WidgetName -> IO RadioMenuItem

see radioMenuItemNew

  • The supplied name can later be used to lookup the widget in the global store.
newRadioMenuItemWithLabel :: String -> IO RadioMenuItem
see radioMenuItemNewWithLabel
newNamedRadioMenuItemWithLabel :: WidgetName -> String -> IO RadioMenuItem

see radioMenuItemNewWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newRadioMenuItemJoinGroup :: RadioMenuItem -> IO RadioMenuItem
see radioMenuNewItemJoinGroup
newNamedRadioMenuItemJoinGroup :: WidgetName -> RadioMenuItem -> IO RadioMenuItem

see radioMenuNewItemJoinGroup

  • The supplied name can later be used to lookup the widget in the global store.
newRadioMenuItemJoinGroupWithLabel :: RadioMenuItem -> String -> IO RadioMenuItem
see radioMenuItemNewJoinGroupWithLabel
newNamedRadioMenuItemJoinGroupWithLabel :: WidgetName -> RadioMenuItem -> String -> IO RadioMenuItem

see radioMenuItemNewJoinGroupWithLabel

  • The supplied name can later be used to lookup the widget in the global store.
newTearoffMenuItem :: IO TearoffMenuItem
see tearoffMenuItemNew
newNamedTearoffMenuItem :: WidgetName -> IO TearoffMenuItem

see tearoffMenuItemNew

  • The supplied name can later be used to lookup the widget in the global store.
newWindow :: IO Window
see windowNew
newNamedWindow :: WidgetName -> IO Window

see windowNew

  • The supplied name can later be used to lookup the widget in the global store.
newDialog :: IO Dialog
see dialogNew
newNamedDialog :: WidgetName -> IO Dialog

see dialogNew

  • The supplied name can later be used to lookup the widget in the global store.
newEventBox :: IO EventBox
see eventBoxNew
newNamedEventBox :: WidgetName -> IO EventBox

see colorSelectionDialogNew

newColorSelectionDialog :: WidgetName -> IO ColorSelectionDialog newColorSelectionDialog name = newNamedWidget name $ colorSelectionDialogNew

see fileSelectionNew

newFileSelection :: WidgetName -> IO FileSelection newFileSelection name = newNamedWidget name $ fileSelectionNew

see fontSelectionDialogNew

newFontSelectionDialog :: WidgetName -> IO FontSelectionDialog newFontSelectionDialog name = newNamedWidget name $ fontSelectionDialogNew

see plugNew

  • The supplied name can later be used to lookup the widget in the global store.

newNamedPlug :: WidgetName -> XID -> IO Plug newNamedPlug name wn = newNamedWidget name $ plugNew wn

see plugNew

newPlug :: XID -> IO Plug newPlug = plugNew

see eventBoxNew

  • The supplied name can later be used to lookup the widget in the global store.
newHandleBox :: IO HandleBox
see handleBoxNew
newNamedHandleBox :: WidgetName -> IO HandleBox

see handleBoxNew

  • The supplied name can later be used to lookup the widget in the global store.
newScrolledWindow :: Maybe Adjustment -> Maybe Adjustment -> IO ScrolledWindow
see scrolledWindowNew
newNamedScrolledWindow :: WidgetName -> Maybe Adjustment -> Maybe Adjustment -> IO ScrolledWindow

see scrolledWindowNew

  • The supplied name can later be used to lookup the widget in the global store.
newViewport :: Adjustment -> Adjustment -> IO Viewport
see viewportNew
newNamedViewport :: WidgetName -> Adjustment -> Adjustment -> IO Viewport

see viewportNew

  • The supplied name can later be used to lookup the widget in the global store.
newVBox :: Bool -> Int -> IO VBox
see vBoxNew
newNamedVBox :: WidgetName -> Bool -> Int -> IO VBox

see vBoxNew

  • The supplied name can later be used to lookup the widget in the global store.
newHBox :: Bool -> Int -> IO HBox
see hBoxNew
newNamedHBox :: WidgetName -> Bool -> Int -> IO HBox

see colorSelectionNew

newColorSelection :: WidgetName -> IO colorSelection newColorSelection name = newNamedWidget name $ colorSelectionNew

see fontSelectionNew

newFontSelection :: WidgetName -> IO FontSelection newFontSelection name = newNamedWidget name $ fontSelectionNew

see hBoxNew

  • The supplied name can later be used to lookup the widget in the global store.
newCombo :: IO Combo
see comboNew
newNamedCombo :: WidgetName -> IO Combo

see comboNew

  • The supplied name can later be used to lookup the widget in the global store.
newStatusbar :: IO Statusbar
see statusbarNew
newNamedStatusbar :: WidgetName -> IO Statusbar

see statusbarNew

  • The supplied name can later be used to lookup the widget in the global store.
newHPaned :: IO HPaned
see hPanedNew
newNamedHPaned :: WidgetName -> IO HPaned

see hPanedNew

  • The supplied name can later be used to lookup the widget in the global store.
newVPaned :: IO VPaned
see vPanedNew
newNamedVPaned :: WidgetName -> IO VPaned

see vPanedNew

  • The supplied name can later be used to lookup the widget in the global store.
newLayout :: Maybe Adjustment -> Maybe Adjustment -> IO Layout
see layoutNew
newNamedLayout :: WidgetName -> Maybe Adjustment -> Maybe Adjustment -> IO Layout

see layoutNew

  • The supplied name can later be used to lookup the widget in the global store.
newMenu :: IO Menu
see menuNew
newNamedMenu :: WidgetName -> IO Menu

see menuNew

  • The supplied name can later be used to lookup the widget in the global store.
newMenuBar :: IO MenuBar
see menuBarNew
newNamedMenuBar :: WidgetName -> IO MenuBar

see menuBarNew

  • The supplied name can later be used to lookup the widget in the global store.
newNotebook :: IO Notebook
see notebookNew
newNamedNotebook :: WidgetName -> IO Notebook

see notebookNew

  • The supplied name can later be used to lookup the widget in the global store.
newTable :: Int -> Int -> Bool -> IO Table
see tableNew
newNamedTable :: WidgetName -> Int -> Int -> Bool -> IO Table

see socketNew

  • The supplied name can later be used to lookup the widget in the global store.

newNamedSocket :: WidgetName -> IO Socket newNamedSocket name = newNamedWidget name $ socketNew

see socketNew

newSocket :: IO Socket newSocket = socketNew

see tableNew

  • The supplied name can later be used to lookup the widget in the global store.
newTextView :: IO TextView
see textViewNew
newNamedTextView :: WidgetName -> IO TextView

see textViewNew

  • The supplied name can later be used to lookup the widget in the global store.
newToolbar :: IO Toolbar
see toolbarNew
newNamedToolbar :: WidgetName -> IO Toolbar

see toolbarNew

  • The supplied name can later be used to lookup the widget in the global store.
newCalendar :: IO Calendar
see calendarNew
newNamedCalendar :: WidgetName -> IO Calendar

see calendarNew

  • The supplied name can later be used to lookup the widget in the global store.
newEntry :: IO Entry
see entryNew
newNamedEntry :: WidgetName -> IO Entry

see drawingAreaNew

  • The supplied name can later be used to lookup the widget in the global store.

newNamedDrawingArea :: WidgetName -> IO DrawingArea newNamedDrawingArea name = newNamedWidget name $ drawingAreaNew

see drawingAreaNew

newDrawingArea :: IO DrawingArea newDrawingArea = drawingAreaNew

see entryNew

  • The supplied name can later be used to lookup the widget in the global store.
newSpinButton :: Adjustment -> Double -> Int -> IO SpinButton
see spinButtonNew
newNamedSpinButton :: String -> Adjustment -> Double -> Int -> IO SpinButton

see spinButtonNew

  • The supplied name can later be used to lookup the widget in the global store.
newSpinButtonWithRange :: Double -> Double -> Double -> IO SpinButton
see spinButtonNewWithRange
newNamedSpinButtonWithRange :: WidgetName -> Double -> Double -> Double -> IO SpinButton

see spinButtonNewWithRange

  • The supplied name can later be used to lookup the widget in the global store.
newHScale :: Adjustment -> IO HScale
see hScaleNew
newNamedHScale :: WidgetName -> Adjustment -> IO HScale

see hScaleNew

  • The supplied name can later be used to lookup the widget in the global store.
newVScale :: Adjustment -> IO VScale
see vScaleNew
newNamedVScale :: WidgetName -> Adjustment -> IO VScale

see vScaleNew

  • The supplied name can later be used to lookup the widget in the global store.
newHScrollbar :: Adjustment -> IO HScrollbar
see hScrollbarNew
newNamedHScrollbar :: WidgetName -> Adjustment -> IO HScrollbar

see hScrollbarNew

  • The supplied name can later be used to lookup the widget in the global store.
newVScrollbar :: Adjustment -> IO VScrollbar
see vScrollbarNew
newNamedVScrollbar :: WidgetName -> Adjustment -> IO VScrollbar

see vScrollbarNew

  • The supplied name can later be used to lookup the widget in the global store.
newHSeparator :: IO HSeparator
see hSeparatorNew
newNamedHSeparator :: WidgetName -> IO HSeparator

see hSeparatorNew

  • The supplied name can later be used to lookup the widget in the global store.
newVSeparator :: IO VSeparator
see vSeparatorNew
newNamedVSeparator :: WidgetName -> IO VSeparator

see vSeparatorNew

  • The supplied name can later be used to lookup the widget in the global store.
newProgressBar :: IO ProgressBar
see progressBarNew
newNamedProgressBar :: WidgetName -> IO ProgressBar

see progressBarNew

  • The supplied name can later be used to lookup the widget in the global store.
newAdjustment :: Double -> Double -> Double -> Double -> Double -> Double -> IO Adjustment
see adjustmentNew
newTooltips :: IO Tooltips

see iMContextNew

newIMContext :: IO iMContext newIMContext = iMContextNew

see iMMulticontextNew

newIMMulticontext :: IO iMMulticontext newIMMulticontext = iMMulticontextNew

see itemFactoryNew

newItemFactory :: IO ItemFactory newItemFactory = itemFactoryNew

see tooltipsNew

newTreeView :: TreeModelClass tm => tm -> IO TreeView
newNamedTreeView :: TreeModelClass tm => WidgetName -> tm -> IO TreeView
newTreeViewWithModel :: TreeModelClass tm => tm -> IO TreeView
see textViewNewWithModel
newNamedTreeViewWithModel :: TreeModelClass tm => WidgetName -> tm -> IO TreeView

see textViewNewWithModel

  • The supplied name can later be used to lookup the widget in the global store.
newTreeViewColumn :: IO TreeViewColumn
see treeViewColumnNew
newIconFactory :: IO IconFactory
see name
Produced by Haddock version 0.7