1{-# LANGUAGE CPP #-}
2{-# LANGUAGE ScopedTypeVariables #-}
3-- -*-haskell-*-
4--  GIMP Toolkit (GTK) Widget Label
5--
6--  Author : Manuel M. T. Chakravarty, Axel Simon, Andy Stewart
7--
8--  Created: 2 May 2001
9--
10--  Copyright (C) 1999-2005 Axel Simon
11--  Copyright (C) 2009 Andy Stewart
12--
13--  This library is free software; you can redistribute it and/or
14--  modify it under the terms of the GNU Lesser General Public
15--  License as published by the Free Software Foundation; either
16--  version 2.1 of the License, or (at your option) any later version.
17--
18--  This library is distributed in the hope that it will be useful,
19--  but WITHOUT ANY WARRANTY; without even the implied warranty of
20--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21--  Lesser General Public License for more details.
22--
23-- |
24-- Maintainer  : gtk2hs-users@lists.sourceforge.net
25-- Stability   : provisional
26-- Portability : portable (depends on GHC)
27--
28-- A widget that displays a small to medium amount of text
29--
30module Graphics.UI.Gtk.Display.Label (
31-- * Detail
32--
33-- | The 'Label' widget displays a small amount of text. As the name implies,
34-- most labels are used to label another widget such as a 'Button', a
35-- 'MenuItem', or a 'OptionMenu'.
36
37-- ** Mnemonics
38--
39-- | Labels may contain mnemonics. Mnemonics are underlined characters in the
40-- label, used for keyboard navigation. Mnemonics are created by providing a
41-- string with an underscore before the mnemonic character, such as
42-- @\"_File\"@, to the functions 'labelNewWithMnemonic' or
43-- 'labelSetTextWithMnemonic'.
44--
45-- Mnemonics automatically activate any activatable widget the label is
46-- inside, such as a 'Button'; if the label is not inside the mnemonic's target
47-- widget, you have to tell the label about the target using
48-- 'labelSetMnemonicWidget'. Here's a simple example where the label is inside
49-- a button: There's a convenience function to create buttons with a mnemonic
50-- label already inside: To create a mnemonic for a widget alongside the label,
51-- such as a 'Entry', you have to point the label at the entry with
52-- 'labelSetMnemonicWidget':
53--
54-- >   -- Pressing Alt+H will activate this button
55-- >   button <- buttonNew
56-- >   label <- labelNewWithMnemonic "_Hello"
57-- >   containerAdd button label
58--
59-- >   -- Pressing Alt+H will activate this button
60-- >   button <- buttonNewWithMnemonic "_Hello"
61--
62-- >   -- Pressing Alt+H will focus the entry
63-- >   entry <- entryNew
64-- >   label <- labelNewWithMnemonic "_Hello"
65-- >   labelSetMnemonicWidget label entry
66
67-- ** Markup (styled text)
68--
69-- | To make it easy to format text in a label (changing colors, fonts, etc.),
70-- label text can be provided in a simple markup format. Here's how to create a
71-- label with a small font: (See complete documentation of available tags in
72-- the Pango manual.)
73--
74-- >   label <- labelNew Nothing
75-- >   labelSetMarkup label "<small>Small text</small>"
76--
77-- The markup passed to 'labelSetMarkup' must be valid; for example, literal
78-- \<\/>\/& characters must be escaped as @\"&lt;\"@, @\"&gt;\"@, and
79-- @\"&amp;@\". If you pass
80-- text obtained from the user, file, or a network to 'labelSetMarkup', you\'ll
81-- want to escape it with 'Graphics.Rendering.Pango.Layout.escapeMarkup'.
82
83-- ** Selectable labels
84--
85-- | Labels can be made selectable with 'labelSetSelectable'. Selectable
86-- labels allow the user to copy the label contents to the clipboard. Only
87-- labels that contain useful-to-copy information - such as error messages -
88-- should be made selectable.
89
90-- ** Text layout
91--
92-- | A label can contain any number of paragraphs, but will have performance
93-- problems if it contains more than a small number. Paragraphs are separated
94-- by newlines or other paragraph separators understood by Pango.
95--
96-- Labels can automatically wrap text if you call 'labelSetLineWrap'.
97--
98-- 'labelSetJustify' sets how the lines in a label align with one another.
99-- If you want to set how the label as a whole aligns in its available space,
100-- see 'Graphics.UI.Gtk.Abstract.Misc.miscSetAlignment'.
101--
102
103-- * Class Hierarchy
104-- |
105-- @
106-- |  'GObject'
107-- |   +----'Object'
108-- |         +----'Widget'
109-- |               +----'Misc'
110-- |                     +----Label
111-- |                           +----'AccelLabel'
112-- |                           +----'TipsQuery'
113-- @
114
115-- * Types
116  Label,
117  LabelClass,
118  castToLabel, gTypeLabel,
119  toLabel,
120
121-- * Constructors
122  labelNew,
123  labelNewWithMnemonic,
124
125-- * Methods
126  labelSetText,
127  labelSetLabel,
128  labelSetTextWithMnemonic,
129  labelSetMarkup,
130  labelSetMarkupWithMnemonic,
131  labelSetMnemonicWidget,
132  labelGetMnemonicWidget,
133  KeyVal,
134  labelGetMnemonicKeyval,
135  labelSetUseMarkup,
136  labelGetUseMarkup,
137  labelSetUseUnderline,
138  labelGetUseUnderline,
139  labelGetText,
140  labelGetLabel,
141  labelSetAttributes,
142  labelGetAttributes,
143  labelSetPattern,
144  Justification(..),
145  labelSetJustify,
146  labelGetJustify,
147  labelGetLayout,
148  labelSetLineWrap,
149  labelGetLineWrap,
150  labelSetLineWrapMode,
151  labelGetLineWrapMode,
152  labelSetSelectable,
153  labelGetSelectable,
154  labelSelectRegion,
155  labelGetSelectionBounds,
156  labelGetLayoutOffsets,
157#if GTK_CHECK_VERSION(2,6,0)
158  labelSetEllipsize,
159  labelGetEllipsize,
160  labelSetWidthChars,
161  labelGetWidthChars,
162  labelSetMaxWidthChars,
163  labelGetMaxWidthChars,
164  labelSetSingleLineMode,
165  labelGetSingleLineMode,
166  labelSetAngle,
167  labelGetAngle,
168#endif
169
170-- * Attributes
171  labelLabel,
172  labelUseMarkup,
173  labelUseUnderline,
174  labelJustify,
175  labelWrap,
176  labelWrapMode,
177  labelSelectable,
178  labelMnemonicWidget,
179  labelMnemonicKeyval,
180  labelPattern,
181  labelCursorPosition,
182  labelSelectionBound,
183#if GTK_CHECK_VERSION(2,6,0)
184  labelEllipsize,
185  labelWidthChars,
186  labelSingleLineMode,
187  labelAngle,
188  labelAttributes,
189  labelMaxWidthChars,
190#endif
191  labelLineWrap,
192  labelText,
193
194-- * Signals
195  labelActiveCurrentLink,
196  labelActiveLink,
197  labelCopyClipboard,
198  labelMoveCursor,
199  labelPopulatePopup
200  ) where
201
202import Control.Monad    (liftM)
203import Data.Text        (Text)
204import qualified Data.Text as T (pack)
205
206import System.Glib.FFI
207import System.Glib.UTFString
208import System.Glib.Attributes
209import System.Glib.Properties
210{#import Graphics.Rendering.Pango.Layout#}
211import Graphics.UI.Gtk.Abstract.Object  (makeNewObject)
212{#import Graphics.UI.Gtk.Types#}
213import Graphics.Rendering.Pango.Attributes ( withAttrList, fromAttrList)
214import Graphics.UI.Gtk.Gdk.Keys         (KeyVal)
215import Graphics.UI.Gtk.General.Enums    (Justification(..), MovementStep (..))
216{#import Graphics.Rendering.Pango.BasicTypes#}  (PangoLayout(PangoLayout),
217                                         makeNewPangoString, PangoString(..) )
218import Graphics.Rendering.Pango.Types (mkPangoLayoutRaw, PangoLayoutRaw)
219import Graphics.Rendering.Pango.Enums   (PangoAttribute)
220import Data.IORef ( newIORef )
221{#import Graphics.UI.Gtk.Signals#}
222
223{# context lib="gtk" prefix="gtk" #}
224
225--------------------
226-- Constructors
227
228-- | Creates a new label with the given text inside it. You can pass @Nothing@
229-- to get an empty label widget.
230--
231labelNew :: GlibString string => Maybe string -> IO Label
232labelNew str =
233  makeNewObject mkLabel $
234  liftM (castPtr :: Ptr Widget -> Ptr Label) $
235  maybeWith withUTFString str $ \strPtr ->
236  {# call label_new #}
237    strPtr
238
239-- | Creates a new 'Label', containing the text in @str@.
240--
241-- If characters in @str@ are preceded by an underscore, they are
242-- underlined. If you need a literal underscore character in a label, use
243-- \'__\' (two underscores). The first underlined character represents a
244-- keyboard accelerator called a mnemonic. The mnemonic key can be used to
245-- activate another widget, chosen automatically, or explicitly using
246-- 'labelSetMnemonicWidget'.
247--
248-- If 'labelSetMnemonicWidget' is not called, then the first activatable
249-- ancestor of the 'Label' will be chosen as the mnemonic widget. For instance,
250-- if the label is inside a button or menu item, the button or menu item will
251-- automatically become the mnemonic widget and be activated by the mnemonic.
252--
253labelNewWithMnemonic :: GlibString string
254 => string   -- ^ @str@ - The text of the label, with an underscore in front
255             -- of the mnemonic character
256 -> IO Label
257labelNewWithMnemonic str =
258  makeNewObject mkLabel $
259  liftM (castPtr :: Ptr Widget -> Ptr Label) $
260  withUTFString str $ \strPtr ->
261  {# call label_new_with_mnemonic #}
262    strPtr
263
264--------------------
265-- Methods
266
267-- | Sets the text within the 'Label' widget. It overwrites any text that was
268-- there before.
269--
270-- This will also clear any previously set mnemonic accelerators.
271--
272labelSetText :: (LabelClass self, GlibString string) => self -> string -> IO ()
273labelSetText self str =
274  withUTFString str $ \strPtr ->
275  {# call label_set_text #}
276    (toLabel self)
277    strPtr
278
279-- | Sets the text of the label. The label is interpreted as including
280-- embedded underlines and\/or Pango markup depending on the markup and
281-- underline properties.
282--
283labelSetLabel :: (LabelClass self, GlibString string) => self -> string -> IO ()
284labelSetLabel self str =
285  withUTFString str $ \strPtr ->
286  {# call label_set_label #}
287    (toLabel self)
288    strPtr
289
290-- | Sets a PangoAttrList; the attributes in the list are applied to the label
291-- text.
292--
293-- Note: The attributes set with this function will be applied and merged with
294-- any other attributes previously effected by way of the 'labelUseUnderline' or
295-- 'labelUseMarkup' properties. While it is not recommended to mix markup strings
296-- with manually set attributes, if you must; know that the attributes will be
297-- applied to the label after the markup string is parsed.
298--
299labelSetAttributes :: LabelClass self => self
300 -> [PangoAttribute]   -- ^ @attr@ 'PangoAttribute'
301 -> IO ()
302labelSetAttributes self attrs = do
303  (txt :: Text) <- labelGetText self
304  ps <- makeNewPangoString txt
305  withAttrList ps attrs $ \alPtr ->
306    {#call unsafe label_set_attributes #} (toLabel self) alPtr
307
308-- | Gets the attribute list that was set on the label using 'labelSetAttributes', if any.
309-- This function does not reflect attributes that come from the labels markup (see 'labelSetMarkup').
310-- If you want to get the effective attributes for the label, use 'layoutGetAttributes' ('labelGetLayout' (label)).
311--
312labelGetAttributes :: LabelClass self => self
313 -> IO [PangoAttribute]          -- ^ return the attribute list, or Emtpy if none was set.
314labelGetAttributes self = do
315  (txt :: Text) <- labelGetText self
316  (PangoString correct _ _ ) <- makeNewPangoString txt
317  attrListPtr <- {# call unsafe label_get_attributes #} (toLabel self)
318  attr <- fromAttrList correct attrListPtr
319  return $ concat attr
320
321-- | Parses @str@ which is marked up with the Pango text markup language,
322-- as defined in "Graphics.Rendering.Pango.Markup",
323-- setting the label's text and attribute list based on the parse results. If
324-- the @str@ is external data, you may need to escape it.
325--
326labelSetMarkup :: (LabelClass self, GlibString markup) => self
327 -> markup -- ^ @str@ - a markup string (see Pango markup format)
328 -> IO ()
329labelSetMarkup self str =
330  withUTFString str $ \strPtr ->
331  {# call label_set_markup #}
332    (toLabel self)
333    strPtr
334
335-- | Parses @str@ which is marked up with the Pango text markup language,
336-- as defined in "Graphics.Rendering.Pango.Markup",
337-- setting the label's text and attribute list based on the parse results. If
338-- characters in @str@ are preceded by an underscore, they are underlined
339-- indicating that they represent a keyboard accelerator called a mnemonic.
340--
341-- The mnemonic key can be used to activate another widget, chosen
342-- automatically, or explicitly using 'labelSetMnemonicWidget'.
343--
344labelSetMarkupWithMnemonic :: (LabelClass self, GlibString markup) => self
345 -> markup -- ^ @str@ - a markup string (see Pango markup format)
346 -> IO ()
347labelSetMarkupWithMnemonic self str =
348  withUTFString str $ \strPtr ->
349  {# call label_set_markup_with_mnemonic #}
350    (toLabel self)
351    strPtr
352
353-- | Underline parts of the text, odd indices of the list represent underlined
354-- parts.
355--
356labelSetPattern :: LabelClass l => l -> [Int] -> IO ()
357labelSetPattern self list =
358  withUTFString (T.pack str) $
359  {# call label_set_pattern #}
360    (toLabel self)
361  where
362    str = concat $ zipWith replicate list (cycle ['_',' '])
363
364-- | Sets the alignment of the lines in the text of the label relative to each
365-- other. 'JustifyLeft' is the default value when the widget is first created
366-- with 'labelNew'. If you instead want to set the alignment of the label as a
367-- whole, use 'Graphics.UI.Gtk.Abstract.Misc.miscSetAlignment' instead.
368-- 'labelSetJustify' has no effect on labels containing only a single line.
369--
370labelSetJustify :: LabelClass self => self -> Justification -> IO ()
371labelSetJustify self jtype =
372  {# call label_set_justify #}
373    (toLabel self)
374    ((fromIntegral . fromEnum) jtype)
375
376-- | Returns the justification of the label. See 'labelSetJustify'.
377--
378labelGetJustify :: LabelClass self => self -> IO Justification
379labelGetJustify self =
380  liftM (toEnum . fromIntegral) $
381  {# call unsafe label_get_justify #}
382    (toLabel self)
383
384-- | Gets the 'PangoLayout' used to display the label. The layout is useful to
385-- e.g. convert text positions to pixel positions, in combination with
386-- 'labelGetLayoutOffsets'.
387--
388labelGetLayout :: LabelClass self => self -> IO PangoLayout
389labelGetLayout self = do
390  plr <- makeNewGObject mkPangoLayoutRaw $
391    {# call unsafe label_get_layout #} (toLabel self)
392  (txt :: Text) <- labelGetText self
393  ps <- makeNewPangoString txt
394  psRef <- newIORef ps
395  return (PangoLayout psRef plr)
396
397-- | Toggles line wrapping within the 'Label' widget. @True@ makes it break
398-- lines if text exceeds the widget's size. @False@ lets the text get cut off
399-- by the edge of the widget if it exceeds the widget size.
400--
401labelSetLineWrap :: LabelClass self => self
402 -> Bool  -- ^ @wrap@ - the setting
403 -> IO ()
404labelSetLineWrap self wrap =
405  {# call label_set_line_wrap #}
406    (toLabel self)
407    (fromBool wrap)
408
409-- | Returns whether lines in the label are automatically wrapped. See
410-- 'labelSetLineWrap'.
411--
412labelGetLineWrap :: LabelClass self => self
413 -> IO Bool -- ^ returns @True@ if the lines of the label are automatically
414            -- wrapped.
415labelGetLineWrap self =
416  liftM toBool $
417  {# call unsafe label_get_line_wrap #}
418    (toLabel self)
419
420-- | If line wrapping is on (see 'labelSetLineWrap') this controls how the line wrapping is done.
421-- The default is 'WrapWholeWords' which means wrap on word boundaries.
422--
423-- * Available since Gtk+ version 2.10
424--
425labelSetLineWrapMode :: LabelClass self => self
426 -> LayoutWrapMode  -- ^ @wrapMode@ - the line wrapping mode
427 -> IO ()
428labelSetLineWrapMode self wrapMode =
429  {# call label_set_line_wrap_mode #}
430    (toLabel self)
431    (fromIntegral (fromEnum wrapMode))
432
433-- | Returns line wrap mode used by the label. See 'labelSetLineWrapMode'.
434--
435-- * Available since Gtk+ version 2.10
436--
437labelGetLineWrapMode :: LabelClass self => self
438 -> IO LayoutWrapMode  -- ^ return the line wrapping mode
439labelGetLineWrapMode self = liftM (toEnum . fromIntegral) $
440  {# call label_get_line_wrap_mode #}
441    (toLabel self)
442
443-- | Obtains the coordinates where the label will draw the 'PangoLayout'
444-- representing the text in the label; useful to convert mouse events into
445-- coordinates inside the 'PangoLayout', e.g. to take some action if some part
446-- of the label is clicked. Of course you will need to create a 'EventBox' to
447-- receive the events, and pack the label inside it, since labels are a
448-- \'NoWindow\' widget.
449--
450labelGetLayoutOffsets :: LabelClass self => self -> IO (Int, Int)
451labelGetLayoutOffsets self =
452  alloca $ \xPtr ->
453  alloca $ \yPtr -> do
454  {# call unsafe label_get_layout_offsets #}
455    (toLabel self)
456    xPtr
457    yPtr
458  x <- peek xPtr
459  y <- peek yPtr
460  return (fromIntegral x, fromIntegral y)
461
462-- | If the label has been set so that it has an mnemonic key this function
463-- returns the keyval used for the mnemonic accelerator.
464--
465labelGetMnemonicKeyval :: LabelClass self => self -> IO KeyVal
466labelGetMnemonicKeyval self =
467  liftM fromIntegral $
468  {# call unsafe label_get_mnemonic_keyval #}
469    (toLabel self)
470
471-- | Gets whether the text selectable.
472--
473labelGetSelectable :: LabelClass self => self
474 -> IO Bool -- ^ returns @True@ if the user can copy text from the label
475labelGetSelectable self =
476  liftM toBool $
477  {# call unsafe label_get_selectable #}
478    (toLabel self)
479
480-- | Sets whether the text of the label contains markup in Pango's text markup
481-- language. See 'labelSetMarkup'.
482--
483labelSetUseMarkup :: LabelClass self => self
484 -> Bool  -- ^ @setting@ - @True@ if the label's text should be parsed for
485          -- markup.
486 -> IO ()
487labelSetUseMarkup self setting =
488  {# call label_set_use_markup #}
489    (toLabel self)
490    (fromBool setting)
491
492-- | Returns whether the label's text is interpreted as marked up with the
493-- Pango text markup language. See 'labelSetUseMarkup'.
494--
495labelGetUseMarkup :: LabelClass self => self
496 -> IO Bool -- ^ returns @True@ if the label's text will be parsed for markup.
497labelGetUseMarkup self =
498  liftM toBool $
499  {# call unsafe label_get_use_markup #}
500    (toLabel self)
501
502-- | If @True@, an underline in the text indicates the next character should be
503-- used for the mnemonic accelerator key.
504--
505labelSetUseUnderline :: LabelClass self => self -> Bool -> IO ()
506labelSetUseUnderline self useUnderline =
507  {# call label_set_use_underline #}
508    (toLabel self)
509    (fromBool useUnderline)
510
511-- | Returns whether an embedded underline in the label indicates a mnemonic.
512-- See 'labelSetUseUnderline'.
513--
514labelGetUseUnderline :: LabelClass self => self -> IO Bool
515labelGetUseUnderline self =
516  liftM toBool $
517  {# call unsafe label_get_use_underline #}
518    (toLabel self)
519
520-- | Gets the text from a label widget, as displayed on the screen. This
521-- does not include any embedded underlines indicating mnemonics or Pango
522-- markup. (See 'labelGetLabel')
523--
524labelGetText :: (LabelClass self, GlibString string) => self -> IO string
525labelGetText self =
526  {# call unsafe label_get_text #}
527    (toLabel self)
528  >>= peekUTFString
529
530-- | Gets the text from a label widget including any embedded underlines
531-- indicating mnemonics and Pango markup. (See 'labelGetText').
532--
533labelGetLabel :: (LabelClass self, GlibString string) => self -> IO string
534labelGetLabel self =
535  {# call unsafe label_get_label #}
536    (toLabel self)
537  >>= peekUTFString
538
539-- | Selects a range of characters in the label, if the label is selectable.
540-- See 'labelSetSelectable'. If the label is not selectable, this function has
541-- no effect. If @startOffset@ or @endOffset@ are -1, then the end of the label
542-- will be substituted.
543--
544labelSelectRegion :: LabelClass self => self
545 -> Int   -- ^ @startOffset@ - start offset
546 -> Int   -- ^ @endOffset@ - end offset
547 -> IO ()
548labelSelectRegion self startOffset endOffset =
549  {# call label_select_region #}
550    (toLabel self)
551    (fromIntegral startOffset)
552    (fromIntegral endOffset)
553
554-- | Gets the selected range of characters in the label, if any. If there is
555-- a range selected the result is the start and end of the selection as
556-- character offsets.
557--
558labelGetSelectionBounds :: LabelClass self => self
559 -> IO (Maybe (Int, Int))
560labelGetSelectionBounds self =
561  alloca $ \startPtr ->
562  alloca $ \endPtr -> do
563  isSelection <-
564    liftM toBool $
565    {# call unsafe label_get_selection_bounds #}
566    (toLabel self)
567    startPtr
568    endPtr
569  if isSelection
570    then do start <- peek startPtr
571            end <- peek endPtr
572            return $ Just $ (fromIntegral start, fromIntegral end)
573    else return Nothing
574
575-- | If the label has been set so that it has an mnemonic key (using i.e.
576-- 'labelSetMarkupWithMnemonic', 'labelSetTextWithMnemonic',
577-- 'labelNewWithMnemonic' or the \"use_underline\" property) the label can be
578-- associated with a widget that is the target of the mnemonic. When the label
579-- is inside a widget (like a 'Button' or a 'Notebook' tab) it is automatically
580-- associated with the correct widget, but sometimes (i.e. when the target is a
581-- 'Entry' next to the label) you need to set it explicitly using this
582-- function.
583--
584-- The target widget will be accelerated by emitting \"mnemonic_activate\"
585-- on it. The default handler for this signal will activate the widget if there
586-- are no mnemonic collisions and toggle focus between the colliding widgets
587-- otherwise.
588--
589labelSetMnemonicWidget :: (LabelClass self, WidgetClass widget) => self
590 -> widget -- ^ @widget@ - the target 'Widget'
591 -> IO ()
592labelSetMnemonicWidget self widget =
593  {# call unsafe label_set_mnemonic_widget #}
594    (toLabel self)
595    (toWidget widget)
596
597-- | Retrieves the target of the mnemonic (keyboard shortcut) of this label.
598-- See 'labelSetMnemonicWidget'.
599--
600labelGetMnemonicWidget :: LabelClass self => self
601 -> IO (Maybe Widget) -- ^ returns the target of the label's mnemonic, or
602                      -- @Nothing@ if none has been set and the default
603                      -- algorithm will be used.
604labelGetMnemonicWidget self =
605  maybeNull (makeNewObject mkWidget) $
606  {# call unsafe label_get_mnemonic_widget #}
607    (toLabel self)
608
609-- | Selectable labels allow the user to select text from the label, for
610-- copy-and-paste.
611--
612labelSetSelectable :: LabelClass self => self
613 -> Bool  -- ^ @setting@ - @True@ to allow selecting text in the label
614 -> IO ()
615labelSetSelectable self setting =
616  {# call unsafe label_set_selectable #}
617    (toLabel self)
618    (fromBool setting)
619
620-- | Sets the label's text from the given string. If characters in the string are
621-- preceded by an underscore, they are underlined indicating that they
622-- represent a keyboard accelerator called a mnemonic. The mnemonic key can be
623-- used to activate another widget, chosen automatically, or explicitly using
624-- 'labelSetMnemonicWidget'.
625--
626labelSetTextWithMnemonic :: (LabelClass self, GlibString string) => self -> string -> IO ()
627labelSetTextWithMnemonic self str =
628  withUTFString str $ \strPtr ->
629  {# call label_set_text_with_mnemonic #}
630    (toLabel self)
631    strPtr
632
633#if GTK_CHECK_VERSION(2,6,0)
634-- | Sets the mode used to ellipsize (add an ellipsis: \"...\") to the text if
635-- there is not enough space to render the entire string.
636--
637-- * Available since Gtk+ version 2.6
638--
639labelSetEllipsize :: LabelClass self => self
640 -> EllipsizeMode -- ^ @mode@ - a 'EllipsizeMode'
641 -> IO ()
642labelSetEllipsize self mode =
643  {# call gtk_label_set_ellipsize #}
644    (toLabel self)
645    ((fromIntegral . fromEnum) mode)
646
647-- | Sets the desired width in characters of @label@ to @nChars@.
648--
649-- * Available since Gtk+ version 2.6
650--
651labelSetWidthChars :: LabelClass self => self
652 -> Int   -- ^ @nChars@ - the new desired width, in characters.
653 -> IO ()
654labelSetWidthChars self nChars =
655  {# call gtk_label_set_width_chars #}
656    (toLabel self)
657    (fromIntegral nChars)
658
659-- | Sets the desired maximum width in characters of @label@ to @nChars@.
660--
661-- * Available since Gtk+ version 2.6
662--
663labelSetMaxWidthChars :: LabelClass self => self
664 -> Int   -- ^ @nChars@ - the new desired maximum width, in characters.
665 -> IO ()
666labelSetMaxWidthChars self nChars =
667  {# call gtk_label_set_max_width_chars #}
668    (toLabel self)
669    (fromIntegral nChars)
670
671-- | Returns the ellipsizing position of the label. See 'labelSetEllipsize'.
672--
673-- * Available since Gtk+ version 2.6
674--
675labelGetEllipsize :: LabelClass self => self
676 -> IO EllipsizeMode -- ^ returns 'EllipsizeMode'
677labelGetEllipsize self =
678  liftM (toEnum . fromIntegral) $
679  {# call gtk_label_get_ellipsize #}
680    (toLabel self)
681
682-- | Retrieves the desired width of @label@, in characters. See
683-- 'labelSetWidthChars'.
684--
685-- * Available since Gtk+ version 2.6
686--
687labelGetWidthChars :: LabelClass self => self
688 -> IO Int -- ^ returns the width of the label in characters.
689labelGetWidthChars self =
690  liftM fromIntegral $
691  {# call gtk_label_get_width_chars #}
692    (toLabel self)
693
694-- | Retrieves the desired maximum width of @label@, in characters. See
695-- 'labelSetWidthChars'.
696--
697-- * Available since Gtk+ version 2.6
698--
699labelGetMaxWidthChars :: LabelClass self => self
700 -> IO Int -- ^ returns the maximum width of the label in characters.
701labelGetMaxWidthChars self =
702  liftM fromIntegral $
703  {# call gtk_label_get_max_width_chars #}
704    (toLabel self)
705
706-- | Returns whether the label is in single line mode.
707--
708-- * Available since Gtk+ version 2.6
709--
710labelGetSingleLineMode :: LabelClass self => self
711 -> IO Bool -- ^ returns @True@ when the label is in single line mode.
712labelGetSingleLineMode self =
713  liftM toBool $
714  {# call gtk_label_get_single_line_mode #}
715    (toLabel self)
716
717-- | Gets the angle of rotation for the label. See gtk_label_set_angle.
718--
719-- * Available since Gtk+ version 2.6
720--
721labelGetAngle :: LabelClass self => self
722 -> IO Double -- ^ returns the angle of rotation for the label
723labelGetAngle self =
724  liftM realToFrac $
725  {# call gtk_label_get_angle #}
726    (toLabel self)
727
728-- | Sets whether the label is in single line mode.
729--
730-- * Available since Gtk+ version 2.6
731--
732labelSetSingleLineMode :: LabelClass self => self
733 -> Bool  -- ^ @singleLineMode@ - @True@ if the label should be in single line
734          -- mode
735 -> IO ()
736labelSetSingleLineMode self singleLineMode =
737  {# call gtk_label_set_single_line_mode #}
738    (toLabel self)
739    (fromBool singleLineMode)
740
741-- | Sets the angle of rotation for the label. An angle of 90 reads from from
742-- bottom to top, an angle of 270, from top to bottom. The angle setting for
743-- the label is ignored if the label is selectable, wrapped, or ellipsized.
744--
745-- * Available since Gtk+ version 2.6
746--
747labelSetAngle :: LabelClass self => self
748 -> Double -- ^ @angle@ - the angle that the baseline of the label makes with
749           -- the horizontal, in degrees, measured counterclockwise
750 -> IO ()
751labelSetAngle self angle =
752  {# call gtk_label_set_angle #}
753    (toLabel self)
754    (realToFrac angle)
755#endif
756
757--------------------
758-- Attributes
759
760-- | The text of the label.
761--
762labelLabel :: (LabelClass self, GlibString string) => Attr self string
763labelLabel = newAttr
764  labelGetLabel
765  labelSetLabel
766
767-- | The text of the label includes XML markup. See pango_parse_markup().
768--
769-- Default value: @False@
770--
771labelUseMarkup :: LabelClass self => Attr self Bool
772labelUseMarkup = newAttr
773  labelGetUseMarkup
774  labelSetUseMarkup
775
776-- | If set, an underline in the text indicates the next character should be
777-- used for the mnemonic accelerator key.
778--
779-- Default value: @False@
780--
781labelUseUnderline :: LabelClass self => Attr self Bool
782labelUseUnderline = newAttr
783  labelGetUseUnderline
784  labelSetUseUnderline
785
786-- | The alignment of the lines in the text of the label relative to each
787-- other. This does NOT affect the alignment of the label within its
788-- allocation.
789--
790-- Default value: 'JustifyLeft'
791--
792labelJustify :: LabelClass self => Attr self Justification
793labelJustify = newAttr
794  labelGetJustify
795  labelSetJustify
796
797-- | If set, wrap lines if the text becomes too wide.
798--
799-- Default value: @False@
800--
801labelWrap :: LabelClass self => Attr self Bool
802labelWrap = newAttrFromBoolProperty "wrap"
803
804-- | If line wrapping is on (see the 'labelWrap' property) this controls how the line wrapping is done.
805-- The default is 'WrapWholeWords', which means wrap on word boundaries.
806--
807-- Default value: 'WrapWholeWords'
808--
809-- * Available since Gtk+ version 2.10
810--
811labelWrapMode :: LabelClass self => Attr self LayoutWrapMode
812labelWrapMode = newAttrFromEnumProperty "wrap-mode"
813                {# call pure unsafe gtk_label_get_type #}
814
815-- | Whether the label text can be selected with the mouse.
816--
817-- Default value: @False@
818--
819labelSelectable :: LabelClass self => Attr self Bool
820labelSelectable = newAttr
821  labelGetSelectable
822  labelSetSelectable
823
824-- | The widget to be activated when the label's mnemonic key is pressed.
825--
826labelMnemonicWidget :: (LabelClass self, WidgetClass widget) => ReadWriteAttr self (Maybe Widget) widget
827labelMnemonicWidget = newAttr
828  labelGetMnemonicWidget
829  labelSetMnemonicWidget
830
831-- | The mnemonic accelerator key for this label.
832--
833-- Default value: 16777215
834--
835labelMnemonicKeyval :: LabelClass self => ReadAttr self Int
836labelMnemonicKeyval = readAttrFromIntProperty "mnemonic-keyval"
837
838-- | A string with _ characters in positions correspond to characters in the text to underline.
839--
840-- Default value: "\\"
841--
842labelPattern :: (LabelClass self, GlibString string) => WriteAttr self string
843labelPattern = writeAttrFromStringProperty "pattern"
844
845-- | The current position of the insertion cursor in chars.
846--
847-- Allowed values: >= 0
848--
849-- Default value: 0
850--
851labelCursorPosition :: LabelClass self => ReadAttr self Int
852labelCursorPosition = readAttrFromIntProperty "cursor-position"
853
854-- | The position of the opposite end of the selection from the cursor in
855-- chars.
856--
857-- Allowed values: >= 0
858--
859-- Default value: 0
860--
861labelSelectionBound :: LabelClass self => ReadAttr self Int
862labelSelectionBound = readAttrFromIntProperty "selection-bound"
863
864#if GTK_CHECK_VERSION(2,6,0)
865-- | The preferred place to ellipsize the string, if the label does not have
866-- enough room to display the entire string, specified as a 'EllipsizeMode'.
867--
868-- Note that setting this property to a value other than 'EllipsizeNone' has
869-- the side-effect that the label requests only enough space to display the
870-- ellipsis \"...\". In particular, this means that ellipsizing labels don't
871-- work well in notebook tabs, unless the tab's tab-expand property is set to
872-- @True@. Other means to set a label's width are
873-- 'Graphics.UI.Gtk.Abstract.Widget.widgetSetSizeRequest' and
874-- 'labelSetWidthChars'.
875--
876-- Default value: 'EllipsizeNone'
877--
878labelEllipsize :: LabelClass self => Attr self EllipsizeMode
879labelEllipsize = newAttr
880  labelGetEllipsize
881  labelSetEllipsize
882
883-- | The desired width of the label, in characters. If this property is set to
884-- -1, the width will be calculated automatically, otherwise the label will
885-- request either 3 characters or the property value, whichever is greater. If
886-- the width-chars property is set to a positive value, then the
887-- max-width-chars property is ignored.
888--
889-- Allowed values: >= -1
890--
891-- Default value: -1
892--
893labelWidthChars :: LabelClass self => Attr self Int
894labelWidthChars = newAttr
895  labelGetWidthChars
896  labelSetWidthChars
897
898-- | Whether the label is in single line mode. In single line mode, the height
899-- of the label does not depend on the actual text, it is always set to ascent
900-- + descent of the font. This can be an advantage in situations where resizing
901-- the label because of text changes would be distracting, e.g. in a statusbar.
902--
903-- Default value: @False@
904--
905labelSingleLineMode :: LabelClass self => Attr self Bool
906labelSingleLineMode = newAttr
907  labelGetSingleLineMode
908  labelSetSingleLineMode
909
910-- | The angle that the baseline of the label makes with the horizontal, in
911-- degrees, measured counterclockwise. An angle of 90 reads from from bottom to
912-- top, an angle of 270, from top to bottom. Ignored if the label is
913-- selectable, wrapped, or ellipsized.
914--
915-- Allowed values: [0,360]
916--
917-- Default value: 0
918--
919labelAngle :: LabelClass self => Attr self Double
920labelAngle = newAttr
921  labelGetAngle
922  labelSetAngle
923
924-- | A list of style attributes to apply to the text of the label.
925labelAttributes :: LabelClass self => Attr self [PangoAttribute]
926labelAttributes = newAttr
927  labelGetAttributes
928  labelSetAttributes
929
930-- | The desired maximum width of the label, in characters. If this property
931-- is set to -1, the width will be calculated automatically, otherwise the
932-- label will request space for no more than the requested number of
933-- characters. If the width-chars property is set to a positive value, then the
934-- max-width-chars property is ignored.
935--
936-- Allowed values: >= -1
937--
938-- Default value: -1
939--
940labelMaxWidthChars :: LabelClass self => Attr self Int
941labelMaxWidthChars = newAttr
942  labelGetMaxWidthChars
943  labelSetMaxWidthChars
944#endif
945
946-- | \'lineWrap\' property. See 'labelGetLineWrap' and 'labelSetLineWrap'
947--
948labelLineWrap :: LabelClass self => Attr self Bool
949labelLineWrap = newAttr
950  labelGetLineWrap
951  labelSetLineWrap
952
953-- | \'text\' property. See 'labelGetText' and 'labelSetText'
954--
955labelText :: (LabelClass self, GlibString string) => Attr self string
956labelText = newAttr
957  labelGetText
958  labelSetText
959
960--------------------
961-- Signals
962
963-- | The 'labelActiveCurrentLink' signal a keybinding signal which gets emitted when the user activates
964-- a link in the label.
965labelActiveCurrentLink :: LabelClass self => Signal self (IO ())
966labelActiveCurrentLink = Signal (connect_NONE__NONE "activate-current-link")
967
968-- | The 'labelActiveLink' signal is emitted when a URI is activated. Default is to use showURI.
969labelActiveLink :: (LabelClass self, GlibString string) => Signal self (string -> IO ())
970labelActiveLink = Signal (connect_GLIBSTRING__NONE "activate-link")
971
972-- | The 'labelCopyClipboard' signal is a keybinding signal which gets emitted to copy the selection to the
973-- clipboard.
974labelCopyClipboard :: LabelClass self => Signal self (IO ())
975labelCopyClipboard = Signal (connect_NONE__NONE "copy-clipboard")
976
977-- | The 'labelMoveCursor' signal is a keybinding signal which gets emitted when the user initiates a cursor
978-- movement. If the cursor is not visible in label, this signal causes the viewport to be moved
979-- instead.
980--
981-- Applications should not connect to it, but may emit it with 'signalEmitByName' if they need to
982-- control the cursor programmatically.
983--
984-- The default bindings for this signal come in two variants, the variant with the Shift modifier
985-- extends the selection, the variant without the Shift modifer does not. There are too many key
986-- combinations to list them all here.
987--
988--   * Arrow keys move by individual characters\/lines
989--   * Ctrl-arrow key combinations move by words\/paragraphs
990--   * Home\/End keys move to the ends of the buffer
991labelMoveCursor :: LabelClass self => Signal self (MovementStep -> Int -> Bool -> IO ())
992labelMoveCursor = Signal (connect_ENUM_INT_BOOL__NONE "move-cursor")
993
994-- | The 'labelPopulatePopup' signal gets emitted before showing the context menu of the label.
995--
996-- If you need to add items to the context menu, connect to this signal and append your menuitems to
997-- the menu.
998labelPopulatePopup :: LabelClass self=> Signal self (Menu -> IO ())
999labelPopulatePopup = Signal (connect_OBJECT__NONE "populate-popup")
1000