1{-# LANGUAGE CPP #-}
2-- -*-haskell-*-
3--  GIMP Toolkit (GTK) CellRendererText TreeView
4--
5--  Author : Axel Simon
6--
7--  Created: 23 May 2001
8--
9--  Copyright (C) 1999-2006 Axel Simon
10--
11--  This library is free software; you can redistribute it and/or
12--  modify it under the terms of the GNU Lesser General Public
13--  License as published by the Free Software Foundation; either
14--  version 2.1 of the License, or (at your option) any later version.
15--
16--  This library is distributed in the hope that it will be useful,
17--  but WITHOUT ANY WARRANTY; without even the implied warranty of
18--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19--  Lesser General Public License for more details.
20--
21-- |
22-- Maintainer  : gtk2hs-users@lists.sourceforge.net
23-- Stability   : provisional
24-- Portability : portable (depends on GHC)
25--
26-- A 'CellRenderer' which displays a single-line text.
27--
28module Graphics.UI.Gtk.ModelView.CellRendererText (
29-- * Detail
30--
31-- | A 'CellRendererText' renders a given text in its cell, using the font,
32-- color and style information provided by its attributes. The text will be
33-- ellipsized if it is too long and the ellipsize property allows it.
34--
35-- If the 'cellMode' is 'CellRendererModeEditable', the 'CellRendererText'
36-- allows the user to edit its text using an 'Entry' widget.
37
38-- * Class Hierarchy
39-- |
40-- @
41-- |  'GObject'
42-- |   +----'Object'
43-- |         +----'CellRenderer'
44-- |               +----CellRendererText
45-- |                     +----'CellRendererCombo'
46-- @
47
48-- * Types
49  CellRendererText,
50  CellRendererTextClass,
51  castToCellRendererText, gTypeCellRendererText,
52  toCellRendererText,
53
54-- * Constructors
55  cellRendererTextNew,
56
57-- * Methods
58  cellRendererTextSetFixedHeightFromFont,
59
60-- * Attributes
61  cellText,
62  cellTextMarkup,
63  --cellTextAttributes,
64  cellTextSingleParagraphMode,
65  cellTextBackground,
66  cellTextBackgroundColor,
67  cellTextBackgroundSet,
68  cellTextForeground,
69  cellTextForegroundColor,
70  cellTextForegroundSet,
71  cellTextEditable,
72  cellTextEditableSet,
73  cellTextFont,
74  cellTextFontDesc,
75  cellTextFamily,
76  cellTextFamilySet,
77  cellTextStyle,
78  cellTextStyleSet,
79  cellTextVariant,
80  cellTextVariantSet,
81  cellTextWeight,
82  cellTextWeightSet,
83  cellTextStretch,
84  cellTextStretchSet,
85  cellTextSize,
86  cellTextSizePoints,
87  cellTextSizeSet,
88  cellTextScale,
89  cellTextScaleSet,
90  cellTextRise,
91  cellTextRiseSet,
92  cellTextStrikethrough,
93  cellTextStrikethroughSet,
94  cellTextUnderline,
95  cellTextUnderlineSet,
96  cellTextLanguage,
97  cellTextLanguageSet,
98#if GTK_CHECK_VERSION(2,6,0)
99  cellTextEllipsize,
100  cellTextEllipsizeSet,
101  cellTextWidthChars,
102#endif
103#if GTK_CHECK_VERSION(2,8,0)
104  cellTextWrapMode,
105  cellTextWrapWidth,
106#endif
107#if GTK_CHECK_VERSION(2,10,0)
108  cellTextAlignment,
109#endif
110
111-- * Signals
112  edited,
113
114-- * Deprecated
115#ifndef DISABLE_DEPRECATED
116  onEdited,
117  afterEdited
118#endif
119  ) where
120
121import Control.Monad    (liftM)
122
123import System.Glib.FFI
124import System.Glib.UTFString
125import System.Glib.Properties
126import System.Glib.Attributes (Attr, WriteAttr)
127import Graphics.UI.Gtk.Abstract.Object          (makeNewObject)
128{#import Graphics.UI.Gtk.Types#}
129{#import Graphics.UI.Gtk.Signals#}
130{#import Graphics.UI.Gtk.ModelView.Types#}
131import Graphics.UI.Gtk.General.Structs          ()
132import Graphics.Rendering.Pango.Enums
133{#import Graphics.Rendering.Pango.BasicTypes#} ( FontDescription(..),
134                                         makeNewFontDescription )
135{#import Graphics.Rendering.Pango.Layout#}      ( LayoutAlignment, LayoutWrapMode )
136
137{# context lib="gtk" prefix="gtk" #}
138
139--------------------
140-- Constructors
141
142-- | Create a new CellRendererText object.
143--
144cellRendererTextNew :: IO CellRendererText
145cellRendererTextNew =
146  makeNewObject mkCellRendererText $
147  liftM (castPtr :: Ptr CellRenderer -> Ptr CellRendererText) $
148  {# call unsafe cell_renderer_text_new #}
149
150--------------------
151-- Methods
152
153-- | Sets the height of a renderer to explicitly be determined by the
154-- 'cellTextFont' and 'Graphics.UI.Gtk.ModelView.CellRenderer.cellYPad'
155-- attribute set on it. Further changes in these properties do not affect the
156-- height, so they must be accompanied by a subsequent call to this function.
157-- Using this function is unflexible, and should really only be used if
158-- calculating the size of a cell is too slow (ie, a massive number of cells
159-- displayed). If @numberOfRows@ is -1, then the fixed height is unset, and
160-- the height is determined by the properties again.
161--
162cellRendererTextSetFixedHeightFromFont :: CellRendererTextClass self => self
163 -> Int   -- ^ @numberOfRows@ - Number of rows of text each cell renderer is
164          -- allocated, or -1
165 -> IO ()
166cellRendererTextSetFixedHeightFromFont self numberOfRows =
167  {# call gtk_cell_renderer_text_set_fixed_height_from_font #}
168    (toCellRendererText self)
169    (fromIntegral numberOfRows)
170
171
172--------------------
173-- Properties
174
175-- | Text background color as a string.
176--
177-- Default value: @\"\"@
178--
179cellTextBackground :: (CellRendererClass self, GlibString string) => WriteAttr self string
180cellTextBackground = writeAttrFromStringProperty "background"
181
182-- | Text background color as a 'Color'.
183--
184cellTextBackgroundColor :: CellRendererClass self => Attr self Color
185cellTextBackgroundColor = newAttrFromBoxedStorableProperty "background-gdk"
186  {# call pure unsafe gdk_color_get_type #}
187
188-- | Whether the 'cellTextBackground'\/'cellTextBackgroundColor' attribute is set.
189--
190-- Default value: @False@
191--
192cellTextBackgroundSet :: CellRendererClass self => Attr self Bool
193cellTextBackgroundSet = newAttrFromBoolProperty "background-set"
194
195-- | Whether the text can be modified by the user.
196--
197cellTextEditable :: CellRendererTextClass self => Attr self Bool
198cellTextEditable = newAttrFromBoolProperty "editable"
199
200-- | Whether the 'cellTextEditable' flag affects text editability.
201--
202cellTextEditableSet :: CellRendererTextClass self => Attr self Bool
203cellTextEditableSet = newAttrFromBoolProperty "editable-set"
204
205#if GTK_CHECK_VERSION(2,6,0)
206-- | Specifies the preferred place to ellipsize the string, if the cell
207--   renderer does not have enough room to display the entire string.
208--   Setting it to 'Graphics.Rendering.Pango.Enums.EllipsizeNone' turns off
209--   ellipsizing. See the 'cellTextWrapWidth' property for another way of
210--   making the text fit into a given width.
211--
212-- * Available in Gtk 2.6 or higher.
213--
214cellTextEllipsize :: CellRendererTextClass self => Attr self EllipsizeMode
215cellTextEllipsize = newAttrFromEnumProperty "ellipsize"
216                {# call pure pango_ellipsize_mode_get_type #}
217
218-- | Whether the 'cellTextEllipsize' tag affects the ellipsize mode.
219--
220-- * Available in Gtk 2.6 or higher.
221--
222cellTextEllipsizeSet :: CellRendererTextClass self => Attr self Bool
223cellTextEllipsizeSet = newAttrFromBoolProperty "ellipsize-set"
224#endif
225
226-- | Name of the font family, e.g. Sans, Helvetica, Times, Monospace.
227--
228cellTextFamily :: (CellRendererTextClass self, GlibString string) => Attr self string
229cellTextFamily = newAttrFromStringProperty "family"
230
231-- | Determines if 'cellTextFamily' has an effect.
232--
233cellTextFamilySet :: CellRendererTextClass self => Attr self Bool
234cellTextFamilySet = newAttrFromBoolProperty "family-set"
235
236-- | Font description as a string.
237--
238cellTextFont :: (CellRendererTextClass self, GlibString string) => Attr self string
239cellTextFont = newAttrFromStringProperty "font"
240
241-- | Font description as a 'Graphics.Rendering.Pango.FontDescription'.
242--
243cellTextFontDesc :: CellRendererTextClass self => Attr self FontDescription
244cellTextFontDesc = newAttrFromBoxedOpaqueProperty makeNewFontDescription
245  (\(FontDescription fd) act -> withForeignPtr fd act) "font-desc"
246  {# call pure unsafe pango_font_description_get_type #}
247
248-- | Text foreground color as a string.
249--
250-- Default value: @\"\"@
251--
252cellTextForeground :: (CellRendererClass self, GlibString string) => WriteAttr self string
253cellTextForeground = writeAttrFromStringProperty "foreground"
254
255-- | Text foreground color as a 'Color'.
256--
257cellTextForegroundColor :: CellRendererClass self => Attr self Color
258cellTextForegroundColor = newAttrFromBoxedStorableProperty "foreground-gdk"
259  {# call pure unsafe gdk_color_get_type #}
260
261-- | Whether the 'cellTextForeground'\/'cellTextForegroundColor' attribute is set.
262--
263-- Default value: @False@
264--
265cellTextForegroundSet :: CellRendererClass self => Attr self Bool
266cellTextForegroundSet = newAttrFromBoolProperty "foreground-set"
267
268-- | The language this text is in, as an ISO code. Pango can use this as
269--   a hint when rendering the text. If you don't understand this parameter,
270--   you probably don't need it.
271--
272cellTextLanguage :: (CellRendererTextClass self, GlibString string) => Attr self (Maybe string)
273cellTextLanguage = newAttrFromMaybeStringProperty "language"
274
275-- | Whether the 'cellTextLanguage' tag is used, default is @False@.
276--
277cellTextLanguageSet :: CellRendererTextClass self => Attr self Bool
278cellTextLanguageSet = newAttrFromBoolProperty "language-set"
279
280-- | Define a markup string instead of a text. See 'cellText'.
281--
282cellTextMarkup :: (CellRendererTextClass cr, GlibString string) => WriteAttr cr (Maybe string)
283cellTextMarkup  = writeAttrFromMaybeStringProperty "markup"
284
285-- %hash c:4e25 d:f7c6
286-- | Offset of text above the baseline (below the baseline if rise is
287--   negative).
288--
289-- Allowed values: >= -2147483647
290--
291-- Default value: 0
292--
293cellTextRise :: CellRendererTextClass self => Attr self Int
294cellTextRise = newAttrFromIntProperty "rise"
295
296-- | Whether the 'cellTextRise' tag is used, default is @False@.
297--
298cellTextRiseSet :: CellRendererTextClass self => Attr self Bool
299cellTextRiseSet = newAttrFromBoolProperty "rise-set"
300
301-- | Font scaling factor. Default is 1.
302--
303cellTextScale :: CellRendererTextClass self => Attr self Double
304cellTextScale = newAttrFromDoubleProperty "scale"
305
306-- | Whether the 'cellTextScale' tag is used, default is @False@.
307--
308cellTextScaleSet :: CellRendererTextClass self => Attr self Bool
309cellTextScaleSet = newAttrFromBoolProperty "scale-set"
310
311-- %hash c:d85f d:9cfb
312-- | Whether or not to keep all text in a single paragraph.
313--
314-- Default value: @False@
315--
316cellTextSingleParagraphMode :: CellRendererTextClass self => Attr self Bool
317cellTextSingleParagraphMode = newAttrFromBoolProperty "single-paragraph-mode"
318
319-- | Font size in points.
320--
321cellTextSize :: CellRendererTextClass self => Attr self Double
322cellTextSize = newAttrFromDoubleProperty "size-points"
323
324-- %hash c:d281 d:3b0c
325-- | Font size in points.
326--
327-- Allowed values: >= 0
328--
329-- Default value: 0
330--
331cellTextSizePoints :: CellRendererTextClass self => Attr self Double
332cellTextSizePoints = newAttrFromDoubleProperty "size-points"
333
334-- | Whether the 'cellTextSize' tag is used, default is @False@.
335--
336cellTextSizeSet :: CellRendererTextClass self => Attr self Bool
337cellTextSizeSet = newAttrFromBoolProperty "size-set"
338
339-- | Font stretch.
340--
341cellTextStretch :: CellRendererTextClass self => Attr self Stretch
342cellTextStretch = newAttrFromEnumProperty "stretch"
343              {# call pure pango_stretch_get_type #}
344
345-- | Whether the 'cellTextStretch' tag is used, default is @False@.
346--
347cellTextStretchSet :: CellRendererTextClass self => Attr self Bool
348cellTextStretchSet = newAttrFromBoolProperty "stretch-set"
349
350-- | Whether to strike through the text.
351--
352cellTextStrikethrough :: CellRendererTextClass self => Attr self Bool
353cellTextStrikethrough = newAttrFromBoolProperty "strikethrough"
354
355-- | Whether the 'cellTextStrikethrough' tag is used, default is @False@.
356--
357cellTextStrikethroughSet :: CellRendererTextClass self => Attr self Bool
358cellTextStrikethroughSet = newAttrFromBoolProperty "strikethrough-set"
359
360-- | Font style (e.g. normal or italics).
361--
362cellTextStyle :: CellRendererTextClass self => Attr self FontStyle
363cellTextStyle = newAttrFromEnumProperty "style"
364            {# call pure pango_style_get_type #}
365
366-- | Whether the 'cellTextStyle' tag is used, default is @False@.
367--
368cellTextStyleSet :: CellRendererTextClass self => Attr self Bool
369cellTextStyleSet = newAttrFromBoolProperty "style-set"
370
371-- | Define the attribute that specifies the text to be rendered. See
372--   also 'cellTextMarkup'.
373--
374cellText :: (CellRendererTextClass cr, GlibString string) => Attr cr string
375cellText  = newAttrFromStringProperty "text"
376
377-- | Style of underline for this text.
378--
379cellTextUnderline :: CellRendererTextClass self => Attr self Underline
380cellTextUnderline = newAttrFromEnumProperty "underline"
381                {# call pure pango_underline_get_type #}
382
383-- | Whether the 'cellTextUnderline' tag is used, default is @False@.
384--
385cellTextUnderlineSet :: CellRendererTextClass self => Attr self Bool
386cellTextUnderlineSet = newAttrFromBoolProperty "underline-set"
387
388-- | Font variant (e.g. small caps).
389--
390cellTextVariant :: CellRendererTextClass self => Attr self Variant
391cellTextVariant = newAttrFromEnumProperty "variant"
392              {# call pure pango_variant_get_type #}
393
394-- | Whether the 'cellTextVariant' tag is used, default is @False@.
395--
396cellTextVariantSet :: CellRendererTextClass self => Attr self Bool
397cellTextVariantSet = newAttrFromBoolProperty "variant-set"
398
399-- | Font weight, default: 400.
400--
401cellTextWeight :: CellRendererTextClass self => Attr self Int
402cellTextWeight = newAttrFromIntProperty "weight"
403
404-- | Whether the 'cellTextWeight' tag is used, default is @False@.
405--
406cellTextWeightSet :: CellRendererTextClass self => Attr self Bool
407cellTextWeightSet = newAttrFromBoolProperty "weight-set"
408
409#if GTK_CHECK_VERSION(2,6,0)
410
411-- | The desired width of the cell, in characters. If this property is set
412--   to @-1@, the width will be calculated automatically, otherwise the cell
413--   will request either 3 characters or the property value, whichever is
414--   greater.
415--
416-- * Available in Gtk 2.6 or higher.
417--
418cellTextWidthChars :: CellRendererTextClass self => Attr self Int
419cellTextWidthChars = newAttrFromIntProperty "width-chars"
420
421#endif
422
423#if GTK_CHECK_VERSION(2,8,0)
424
425-- | Specifies how to break the string into multiple lines, if the cell
426--   renderer does not have enough room to display the entire string.
427--   This property has no effect unless the 'cellTextWrapWidth' property is set.
428--
429-- * Available in Gtk 2.8 or higher.
430--
431cellTextWrapMode :: CellRendererTextClass self => Attr self LayoutWrapMode
432cellTextWrapMode = newAttrFromEnumProperty "wrap-mode"
433               {# call pure pango_wrap_mode_get_type #}
434
435-- | Specifies the width at which the text is wrapped. The wrap-mode
436--   property can be used to influence at what character positions the
437--   line breaks can be placed. Setting wrap-width to @-1@ turns wrapping off.
438--
439-- * Available in Gtk 2.8 or higher.
440--
441cellTextWrapWidth :: CellRendererTextClass self => Attr self Int
442cellTextWrapWidth = newAttrFromIntProperty "wrap-width"
443
444#endif
445
446
447#if GTK_CHECK_VERSION(2,10,0)
448-- %hash c:a59c d:a84a
449-- | Specifies how to align the lines of text with respect to each other.
450--
451-- Note that this property describes how to align the lines of text in case
452-- there are several of them. The
453-- 'Graphics.UI.Gtk.ModelView.CellRenderer.cellXAlign' property of
454-- 'CellRenderer', on the other hand, sets the horizontal alignment of the
455-- whole text.
456--
457-- Default value: 'Graphics.Rendering.Pango.Layout.AlignLeft'
458--
459-- * Available since Gtk+ version 2.10
460--
461cellTextAlignment :: CellRendererTextClass self => Attr self LayoutAlignment
462cellTextAlignment = newAttrFromEnumProperty "alignment"
463                              {# call pure unsafe pango_alignment_get_type #}
464#endif
465
466--------------------
467-- Signals
468
469-- %hash c:a541 d:18f9
470-- | Emitted when the user finished editing a cell.
471--
472-- Whenever editing is finished successfully, this signal is emitted which
473-- indicates that the model should be updated with the supplied value.
474-- The value is always a string which matches the 'cellText' attribute of
475-- 'CellRendererText' (and its derivates like 'CellRendererCombo').
476--
477-- * This signal is not emitted when editing is disabled (see
478--   'cellTextEditable') or when the user aborts editing.
479--
480edited :: (CellRendererTextClass self, GlibString string) =>
481          Signal self (TreePath -> string -> IO ())
482edited = Signal internalEdited
483
484--------------------
485-- Deprecated Signals
486
487#ifndef DISABLE_DEPRECATED
488-- %hash c:76ed
489onEdited :: (CellRendererTextClass self, GlibString string) => self
490 -> (TreePath -> string -> IO ())
491 -> IO (ConnectId self)
492onEdited = internalEdited False
493{-# DEPRECATED onEdited "instead of 'onEdited obj' use 'on obj edited'" #-}
494
495-- %hash c:f70c
496afterEdited :: (CellRendererTextClass self, GlibString string) => self
497 -> (TreePath -> string -> IO ())
498 -> IO (ConnectId self)
499afterEdited = internalEdited True
500{-# DEPRECATED afterEdited "instead of 'afterEdited obj' use 'after obj edited'" #-}
501#endif
502
503internalEdited :: (CellRendererTextClass cr, GlibString string) =>
504                  Bool -> cr ->
505                  (TreePath -> string -> IO ()) ->
506                  IO (ConnectId cr)
507internalEdited after cr user =
508  connect_GLIBSTRING_GLIBSTRING__NONE "edited" after cr $ \path string -> do
509    user (stringToTreePath path) string
510