Gtk2HsContentsIndex
Graphics.UI.Gtk.Layout.Notebook
Description

This widget can display several pages of widgets. Each page can be selected by a tab at the top of the widget. It is useful in dialogs where a lot of information has to be displayed.

TODO

  • The signals focus-tab and select-page are not bound because it is unclear what they mean. As far as I can see they are not emitted anywhere.
Synopsis
data Notebook
class ContainerClass o => NotebookClass o
castToNotebook :: GObjectClass obj => obj -> Notebook
notebookNew :: IO Notebook
notebookAppendPage :: (NotebookClass nb, WidgetClass child) => nb -> child -> String -> IO Int
notebookAppendPageMenu :: (NotebookClass nb, WidgetClass child, WidgetClass tab, WidgetClass menu) => nb -> child -> tab -> menu -> IO Int
notebookPrependPage :: (NotebookClass nb, WidgetClass child) => nb -> child -> String -> IO Int
notebookPrependPageMenu :: (NotebookClass nb, WidgetClass child, WidgetClass tab, WidgetClass menu) => nb -> child -> tab -> menu -> IO Int
notebookInsertPage :: (NotebookClass nb, WidgetClass child) => nb -> child -> String -> Int -> IO Int
notebookInsertPageMenu :: (NotebookClass nb, WidgetClass child, WidgetClass tab, WidgetClass menu) => nb -> child -> tab -> menu -> Int -> IO Int
notebookRemovePage :: NotebookClass nb => nb -> Int -> IO ()
notebookPageNum :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Maybe Int)
notebookSetCurrentPage :: NotebookClass nb => nb -> Int -> IO ()
notebookNextPage :: NotebookClass nb => nb -> IO ()
notebookPrevPage :: NotebookClass nb => nb -> IO ()
notebookReorderChild :: (NotebookClass nb, WidgetClass w) => nb -> w -> Int -> IO ()
data PositionType
= PosLeft
| PosRight
| PosTop
| PosBottom
notebookSetTabPos :: NotebookClass nb => nb -> PositionType -> IO ()
notebookGetTabPos :: NotebookClass nb => nb -> IO PositionType
notebookSetShowTabs :: NotebookClass nb => nb -> Bool -> IO ()
notebookGetShowTabs :: NotebookClass nb => nb -> IO Bool
notebookSetShowBorder :: NotebookClass nb => nb -> Bool -> IO ()
notebookSetScrollable :: NotebookClass nb => nb -> Bool -> IO ()
notebookGetScrollable :: NotebookClass nb => nb -> IO Bool
notebookSetTabBorder :: NotebookClass nb => nb -> Int -> IO ()
notebookSetTabHBorder :: NotebookClass nb => nb -> Int -> IO ()
notebookSetTabVBorder :: NotebookClass nb => nb -> Int -> IO ()
notebookSetPopup :: NotebookClass nb => nb -> Bool -> IO ()
notebookGetCurrentPage :: NotebookClass nb => nb -> IO Int
notebookSetMenuLabel :: (NotebookClass nb, WidgetClass ch, WidgetClass label) => nb -> ch -> Maybe label -> IO ()
notebookGetMenuLabel :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Maybe Label)
notebookSetMenuLabelText :: (NotebookClass nb, WidgetClass ch) => nb -> ch -> String -> IO ()
notebookGetMenuLabelText :: (NotebookClass nb, WidgetClass ch) => nb -> ch -> IO (Maybe String)
notebookGetNthPage :: NotebookClass nb => nb -> Int -> IO (Maybe Widget)
notebookGetNPages :: NotebookClass nb => nb -> IO Int
notebookGetTabLabel :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Maybe Widget)
notebookGetTabLabelText :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Maybe String)
data Packing
= PackRepel
| PackGrow
| PackNatural
data PackType
= PackStart
| PackEnd
notebookQueryTabLabelPacking :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Packing, PackType)
notebookSetTabLabelPacking :: (NotebookClass nb, WidgetClass w) => nb -> w -> Packing -> PackType -> IO ()
notebookSetHomogeneousTabs :: NotebookClass nb => nb -> Bool -> IO ()
notebookSetTabLabel :: (NotebookClass nb, WidgetClass ch, WidgetClass tab) => nb -> ch -> tab -> IO ()
notebookSetTabLabelText :: (NotebookClass nb, WidgetClass ch) => nb -> ch -> String -> IO ()
onSwitchPage :: NotebookClass nb => nb -> (Int -> IO ()) -> IO (ConnectId nb)
afterSwitchPage :: NotebookClass nb => nb -> (Int -> IO ()) -> IO (ConnectId nb)
Documentation
data Notebook
Instances
NotebookClass Notebook
ContainerClass Notebook
WidgetClass Notebook
ObjectClass Notebook
GObjectClass Notebook
class ContainerClass o => NotebookClass o
Instances
NotebookClass Notebook
castToNotebook :: GObjectClass obj => obj -> Notebook
notebookNew :: IO Notebook
Create a new notebook.
notebookAppendPage
:: (NotebookClass nb, WidgetClass child)
=> nb
-> childWidget to use as the contents of the page
-> StringLabel for the page.
-> IO Int

Insert a new tab to the right of the existing tabs.

  • The given label will be used for the label widget of the new tab. In case the context menu is enabled, this name will also appear in the popup menu. If you want to specify something else to go in the tab, use notebookAppendPageMenu.
  • Returns index (starting from 0) of the appended page in the notebook, or -1 if the function fails.
  • This function returned () in Gtk version 2.2.X and earlier
notebookAppendPageMenu
:: (NotebookClass nb, WidgetClass child, WidgetClass tab, WidgetClass menu)
=> nb
-> childWidget to use as the contents of the page
-> tabTab label widget for the page.
-> menuMenu entry for this tab (usually a Label widget).
-> IO Int

Insert a new tab to the right of the existing tabs.

Like notebookAppendPage but allows any widget to be used for the label of the new tab and then entry in the page-switch popup menu.

  • Returns the index (starting from 0) of the appended page in the notebook, or -1 if the function fails.
  • This function returned () in Gtk version 2.2.X and earlier
notebookPrependPage
:: (NotebookClass nb, WidgetClass child)
=> nb
-> childWidget to use as the contents of the page
-> StringLabel for the page.
-> IO Int

Insert a new tab to the left of the existing tabs.

  • The given label will be used for the label widget of the new tab. In case the context menu is enabled, this name will also appear in the popup menu. If you want to specify something else to go in the tab, use notebookPrependPageMenu.
  • Returns index (starting from 0) of the prepended page in the notebook, or -1 if the function fails.
  • This function returned () in Gtk version 2.2.X and earlier
notebookPrependPageMenu
:: (NotebookClass nb, WidgetClass child, WidgetClass tab, WidgetClass menu)
=> nb
-> childWidget to use as the contents of the page
-> tabTab label widget for the page.
-> menuMenu entry for this tab (usually a Label widget).
-> IO Int

Insert a new tab to the left of the existing tabs.

Like notebookPrependPage but allows any widget to be used for the label of the new tab and then entry in the page-switch popup menu.

  • Returns the index (starting from 0) of the prepended page in the notebook, or -1 if the function fails.
  • This function returned () in Gtk version 2.2.X and earlier
notebookInsertPage
:: (NotebookClass nb, WidgetClass child)
=> nb
-> childWidget to use as the contents of the page
-> StringLabel for the page.
-> IntPosition for the new page.
-> IO Int

Insert a new tab at the specified position. That is between pos and pos+1, or -1 to append the page after all other pages.

  • The given label will be used for the label widget of the new tab. In case the context menu is enabled, this name will also appear in the popup menu. If you want to specify something else to go in the tab, use notebookInsertPageMenu.
  • Returns index (starting from 0) of the inserted page in the notebook, or -1 if the function fails.
  • This function returned () in Gtk version 2.2.X and earlier
notebookInsertPageMenu
:: (NotebookClass nb, WidgetClass child, WidgetClass tab, WidgetClass menu)
=> nb
-> childWidget to use as the contents of the page
-> tabTab label widget for the page.
-> menuMenu entry for this tab (usually a Label widget).
-> IntPosition for the new page.
-> IO Int

Insert a new tab at the specified position. That is between pos and pos+1, or -1 to append the page after all other pages.

Like notebookInsertPage but allows any widget to be used for the label of the new tab and then entry in the page-switch popup menu.

  • Returns the index (starting from 0) of the inserted page in the notebook, or -1 if the function fails.
  • This function returned () in Gtk version 2.2.X and earlier
notebookRemovePage :: NotebookClass nb => nb -> Int -> IO ()
Remove a specific page from the notebook, counting from 0.
notebookPageNum :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Maybe Int)

Query the page the child widget is contained in.

  • The function returns the page number if the child was found, Nothing otherwise.
notebookSetCurrentPage :: NotebookClass nb => nb -> Int -> IO ()

Move to the specified page of the notebook.

  • If the position is out of range (e.g. negative) select the last page.
notebookNextPage :: NotebookClass nb => nb -> IO ()

Move to the right neighbour of the current page.

  • Nothing happens if there is no such page.
notebookPrevPage :: NotebookClass nb => nb -> IO ()

Move to the left neighbour of the current page.

  • Nothing happens if there is no such page.
notebookReorderChild :: (NotebookClass nb, WidgetClass w) => nb -> w -> Int -> IO ()
Move a page withing the notebook.
data PositionType
Position a scale's value is drawn relative to the trough
Constructors
PosLeft
PosRight
PosTop
PosBottom
Instances
Enum PositionType
notebookSetTabPos :: NotebookClass nb => nb -> PositionType -> IO ()
Specify at which border the tabs should be drawn.
notebookGetTabPos :: NotebookClass nb => nb -> IO PositionType
Gets the edge at which the tabs for switching pages in the notebook are drawn.
notebookSetShowTabs :: NotebookClass nb => nb -> Bool -> IO ()
Show or hide the tabs of a notebook.
notebookGetShowTabs :: NotebookClass nb => nb -> IO Bool
Returns whether the tabs of the notebook are shown.
notebookSetShowBorder :: NotebookClass nb => nb -> Bool -> IO ()
In case the tabs are not shown, specify whether to draw a border around the notebook.
notebookSetScrollable :: NotebookClass nb => nb -> Bool -> IO ()
Set whether scroll bars will be added in case the notebook has too many tabs to fit the widget size.
notebookGetScrollable :: NotebookClass nb => nb -> IO Bool
Returns whether the tab label area has arrows for scrolling.
notebookSetTabBorder :: NotebookClass nb => nb -> Int -> IO ()

Set the width of the borders of the tab labels.

  • Sets both vertical and horizontal widths.
notebookSetTabHBorder :: NotebookClass nb => nb -> Int -> IO ()

Set the width of the borders of the tab labels.

  • Sets horizontal widths.
notebookSetTabVBorder :: NotebookClass nb => nb -> Int -> IO ()

Set the width of the borders of the tab labels.

  • Sets vertical widths.
notebookSetPopup :: NotebookClass nb => nb -> Bool -> IO ()
Enable or disable context menus with all tabs in it.
notebookGetCurrentPage :: NotebookClass nb => nb -> IO Int

Query the currently selected page.

  • Returns -1 if notebook has no pages.
notebookSetMenuLabel :: (NotebookClass nb, WidgetClass ch, WidgetClass label) => nb -> ch -> Maybe label -> IO ()
Changes the menu label for the page containing the given child widget.
notebookGetMenuLabel :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Maybe Label)

Extract the menu label from the given child.

  • Returns Nothing if child was not found.
notebookSetMenuLabelText :: (NotebookClass nb, WidgetClass ch) => nb -> ch -> String -> IO ()
Creates a new label and sets it as the menu label of the given child widget.
notebookGetMenuLabelText :: (NotebookClass nb, WidgetClass ch) => nb -> ch -> IO (Maybe String)
Retrieves the text of the menu label for the page containing the given child widget.
notebookGetNthPage :: NotebookClass nb => nb -> Int -> IO (Maybe Widget)

Retrieve the child widget at the given position (starting from 0).

  • Returns Nothing if the index is out of bounds.
notebookGetNPages :: NotebookClass nb => nb -> IO Int

Get the number of pages in a notebook.

  • Only available in Gtk 2.2 and higher.
notebookGetTabLabel :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Maybe Widget)

Extract the tab label from the given child.

  • Nothing is returned if no tab label has specifically been set for the child.
notebookGetTabLabelText :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Maybe String)
Retrieves the text of the tab label for the page containing the given child widget.
data Packing
Packing parameters of a widget
Constructors
PackRepel
PackGrow
PackNatural
Instances
Enum Packing
Eq Packing
data PackType
Packing of widgets at start or end in a box
Constructors
PackStart
PackEnd
Instances
Enum PackType
notebookQueryTabLabelPacking :: (NotebookClass nb, WidgetClass w) => nb -> w -> IO (Packing, PackType)
Query the packing attributes of the given child.
notebookSetTabLabelPacking :: (NotebookClass nb, WidgetClass w) => nb -> w -> Packing -> PackType -> IO ()
Set the packing attributes of the given child.
notebookSetHomogeneousTabs :: NotebookClass nb => nb -> Bool -> IO ()
Sets whether the tabs must have all the same size or not.
notebookSetTabLabel :: (NotebookClass nb, WidgetClass ch, WidgetClass tab) => nb -> ch -> tab -> IO ()
Set a new tab label for a given page.
notebookSetTabLabelText :: (NotebookClass nb, WidgetClass ch) => nb -> ch -> String -> IO ()
Creates a new label and sets it as the tab label for the given page.
onSwitchPage :: NotebookClass nb => nb -> (Int -> IO ()) -> IO (ConnectId nb)
This signal is emitted when a new page is selected.
afterSwitchPage :: NotebookClass nb => nb -> (Int -> IO ()) -> IO (ConnectId nb)
Produced by Haddock version 0.6