4.3 Labels

Labels are used a lot in Gtk2Hs, and are relatively simple. Labels emit no signals as they do not have an associated X window. If you need to catch signals, or do clipping, place it inside an EventBox widget, which allows you to catch signals for widgets which do not have their own window, or a button.

To create a new label, use:

labelNew :: Maybe String -> IO Label

labelNewWithMnemonic :: String -> IO Label

With the second function, if characters in the string are preceded by an underscore, they are underlined. If you need a literal underscore character in a label, use "__" (two underscores). The first underlined character represents a keyboard accelerator called a mnemonic. When that key is pressed the activable widget which contains the label (e.g. a button) will be activated. The widget which is to be affected can also be set by labelSetMnemonicWidget.

To change the label's text after creation, or to get the label's text, use the functions:

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

labelGetLabel :: LabelClass self => self -> IO String

or, of course, the generic set or get functions. The space needed for the new string will be automatically adjusted if needed. You can produce multi-line labels by putting line breaks in the label string. If you have multi-line labels the lines can be justified relatively to each other using:

labelSetJustify :: LabelClass self => self -> Justification -> IO ()

where the type Justification has one of four constructors:

The label widget is also capable of line wrapping the text automatically. This can be activated using:

labelSetLineWrap :: LabelClass self => self -> Bool -> IO ()

If you want your label underlined, then you can set a pattern on the label:

labelSetPattern :: LabelClass self => self -> [Int] -> IO ()

The list of Ints marks the underlined parts of the label text alternated by the non-interlined parts. For example, [3, 1, 3] means first three characters underlined, the next not, and the next three underlined.

You can also make text in a label selectable, so the user can copy and paste it, and use some formatting options.

Below is a short example to illustrate a few of these functions. It makes use of the Frame widget to better demonstrate the label styles. A Frame is just an ornament like a HSeparator and a VSeparator but it surrounds the widget and is an instance of Container. Therefore the widget it frames must be added to it with containerAdd. A frame itself can have a label to convey information about its contents.

Label examples

Because all the labels are framed, a function myLabelWithFrameNew is defined, which returns a tuple. Gtk2Hs is truly Haskell, so you can use all the Haskell data types and features. The justifications are pretty obvious, but they only refer to the lines inside the label. So, to right justify label2 itself, you need miscSetAlignment as shown below. The last two widgets in the left horizontal box are packed with boxPackEnd instead of the usual boxPackStart. The button label demonstrates the use of a mnemonic as an accellerator key. Pressing Alt-C on the keyboard has the same effect as clicking the button.

Note: When tested on Fedora 6, pressing Enter or the space bar also had this effect. Also note the effect of the character "y" on the placement of the underline.

import Graphics.UI.Gtk

main:: IO ()
main = do
  initGUI
  window  <- windowNew
  set window [windowTitle := "Labels", containerBorderWidth := 10]
  mainbox <- vBoxNew False 10
  containerAdd window mainbox
  hbox    <- hBoxNew True 5
  boxPackStart mainbox hbox PackNatural 0
  vbox1   <- vBoxNew False 10
  vbox2   <- vBoxNew False 0
  boxPackStart hbox vbox1 PackNatural 0
  boxPackStart hbox vbox2 PackNatural 0

  (label1,frame1) <- myLabelWithFrameNew
  boxPackStart vbox1 frame1 PackNatural 0
  labelSetText label1 "Penny Harter"

  (label2,frame2) <- myLabelWithFrameNew
  boxPackStart vbox1 frame2 PackNatural 0
  labelSetText label2 "broken bowl\nthe pieces\nstill rocking"
  miscSetAlignment label2 0.0 0.0
  hsep1           <- hSeparatorNew
  boxPackStart vbox1 hsep1 PackNatural 10

  (label3,frame3) <- myLabelWithFrameNew
  boxPackStart vbox1 frame3 PackNatural 0
  labelSetText label3 "Gary Snyder"

  (label4,frame4) <- myLabelWithFrameNew
  boxPackStart vbox1 frame4 PackNatural 0
  labelSetText label4 "After weeks of watching the roof leak\nI fixed it tonight\nby moving a single board"
  labelSetJustify label4 JustifyCenter

  (label5,frame5) <- myLabelWithFrameNew
  boxPackStart vbox2 frame5 PackNatural 0
  labelSetText label5 "Kobayashi Issa"

  (label7,frame7) <- myLabelWithFrameNew
  boxPackEnd vbox2 frame7 PackNatural 0
  labelSetText label7 "only one guy and\nonly one fly trying to\nmake the guest room do"
  labelSetJustify label7 JustifyRight

  (label6,frame6) <- myLabelWithFrameNew
  boxPackEnd vbox2 frame6 PackNatural 10
  labelSetText label6 "One Guy"
  frameSetLabel frame6 "Title:"
  labelSetPattern label6 [3, 1, 3]

  button      <- buttonNew
  boxPackEnd mainbox button PackNatural 20
  buttonlabel <- labelNewWithMnemonic "Haiku _Clicked"
  containerAdd button buttonlabel

  widgetShowAll window
  onClicked button (putStrLn "button clicked...")
  onDestroy window mainQuit
  mainGUI


myLabelWithFrameNew :: IO (Label,Frame)
myLabelWithFrameNew = do
  label <- labelNew Nothing
  frame <- frameNew
  containerAdd frame label
  frameSetShadowType frame ShadowOut
  return (label, frame)


-- Haikus quoted from X.J. Kennedy, Dana Gioia, Introduction to Poetry, Longman, 1997