File: CellView.chs

package info (click to toggle)
haskell-gtk 0.11.0-5
  • links: PTS, VCS
  • area: main
  • in suites: squeeze
  • size: 2,920 kB
  • ctags: 82
  • sloc: haskell: 1,929; ansic: 714; sh: 5; makefile: 3
file content (194 lines) | stat: -rw-r--r-- 5,605 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
{-# LANGUAGE CPP #-}
-- -*-haskell-*-
--  GIMP Toolkit (GTK) Widget CellView
--
--  Author : Duncan Coutts
--
--  Created: 4 April 2005
--
--  Copyright (C) 2005 Duncan Coutts
--
--  This library is free software; you can redistribute it and/or
--  modify it under the terms of the GNU Lesser General Public
--  License as published by the Free Software Foundation; either
--  version 2.1 of the License, or (at your option) any later version.
--
--  This library is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
--  Lesser General Public License for more details.
--
-- |
-- Maintainer  : gtk2hs-users@lists.sourceforge.net
-- Stability   : provisional
-- Portability : portable (depends on GHC)
--
-- A widget displaying a single row of a 'TreeModel'
--
-- * Module available since Gtk+ version 2.6
--
module Graphics.UI.Gtk.ModelView.CellView (
-- * Detail
-- 
-- | A 'CellView' displays a single row of a 'TreeModel', using cell renderers
-- just like 'TreeView'. 'CellView' doesn't support some of the more complex
-- features of 'TreeView', like cell editing and drag and drop.

-- * Class Hierarchy
-- |
-- @
-- |  'GObject'
-- |   +----'Object'
-- |         +----'Widget'
-- |               +----CellView
-- @

#if GTK_CHECK_VERSION(2,6,0)
-- * Types
  CellView,
  CellViewClass,
  castToCellView, gTypeCellView,
  toCellView,

-- * Constructors
  cellViewNew,
  cellViewNewWithMarkup,
  cellViewNewWithPixbuf,
  cellViewNewWithText,

-- * Methods
  cellViewSetModel,
  cellViewGetSizeOfRow,
  cellViewSetBackgroundColor,
  cellViewGetCellRenderers,

-- * Attributes
  cellViewBackground
#endif
  ) where

import Control.Monad	(liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import System.Glib.Properties			(writeAttrFromStringProperty)
{#import System.Glib.GList#}
{#import Graphics.UI.Gtk.Types#}
import Graphics.UI.Gtk.Abstract.Object		(makeNewObject)
{#import Graphics.UI.Gtk.ModelView.Types#}
import Graphics.UI.Gtk.General.Structs		(Color, Requisition)

{# context lib="gtk" prefix="gtk" #}

#if GTK_CHECK_VERSION(2,6,0)
--------------------
-- Constructors

-- | Creates a new 'CellView' widget.
--
cellViewNew :: IO CellView
cellViewNew =
  makeNewObject mkCellView $
  liftM (castPtr :: Ptr Widget -> Ptr CellView) $
  {# call gtk_cell_view_new #}

-- | Creates a new 'CellView' widget, adds a 'CellRendererText' to it, and
-- makes its show @markup@. The text can be marked up with the Pango
-- text markup language.
--
cellViewNewWithMarkup :: 
    String      -- ^ @markup@ - the text to display in the cell view
 -> IO CellView
cellViewNewWithMarkup markup =
  makeNewObject mkCellView $
  liftM (castPtr :: Ptr Widget -> Ptr CellView) $
  withUTFString markup $ \markupPtr ->
  {# call gtk_cell_view_new_with_markup #}
    markupPtr

-- | Creates a new 'CellView' widget, adds a 'CellRendererPixbuf' to it, and
-- makes its show @pixbuf@.
--
cellViewNewWithPixbuf :: 
    Pixbuf      -- ^ @pixbuf@ - the image to display in the cell view
 -> IO CellView
cellViewNewWithPixbuf pixbuf =
  makeNewObject mkCellView $
  liftM (castPtr :: Ptr Widget -> Ptr CellView) $
  {# call gtk_cell_view_new_with_pixbuf #}
    pixbuf

-- | Creates a new 'CellView' widget, adds a 'CellRendererText' to it, and
-- makes its show @text@.
--
cellViewNewWithText :: 
    String      -- ^ @text@ - the text to display in the cell view
 -> IO CellView
cellViewNewWithText text =
  makeNewObject mkCellView $
  liftM (castPtr :: Ptr Widget -> Ptr CellView) $
  withUTFString text $ \textPtr ->
  {# call gtk_cell_view_new_with_text #}
    textPtr

--------------------
-- Methods

-- | Sets the model for @cellView@. If @cellView@ already has a model set, it
-- will remove it before setting the new model. If @model@ is @Nothing@, then
-- it will unset the old model.
--
cellViewSetModel :: (CellViewClass self, TreeModelClass model) => self
 -> Maybe model -- ^ @model@ - a 'TreeModel'
 -> IO ()
cellViewSetModel self model =
  {# call gtk_cell_view_set_model #}
    (toCellView self)
    (maybe (TreeModel nullForeignPtr) toTreeModel model)

-- | Returns the size needed by the cell view to display the model
-- row pointed to by @path@.
--
cellViewGetSizeOfRow :: CellViewClass self => self
 -> TreePath            -- ^ @path@ - a 'TreePath'
 -> IO Requisition      -- ^ returns the size requisition
cellViewGetSizeOfRow self path =
  alloca $ \requisitionPtr ->
  withTreePath path $ \path -> do
  {# call gtk_cell_view_get_size_of_row #}
    (toCellView self)
    path
    (castPtr requisitionPtr)
  peek requisitionPtr

-- | Sets the background color of @view@.
--
cellViewSetBackgroundColor :: CellViewClass self => self
 -> Color -- ^ @color@ - the new background color
 -> IO ()
cellViewSetBackgroundColor self color =
  with color $ \colorPtr ->
  {# call gtk_cell_view_set_background_color #}
    (toCellView self)
    (castPtr colorPtr)

-- | Returns the cell renderers which have been added to @cellView@.
--
cellViewGetCellRenderers :: CellViewClass self => self -> IO [CellRenderer]
cellViewGetCellRenderers self =
  {# call gtk_cell_view_get_cell_renderers #}
    (toCellView self)
  >>= fromGList
  >>= mapM (\elemPtr -> makeNewObject mkCellRenderer (return elemPtr))

--------------------
-- Attributes

-- | Background color as a string.
--
-- Default value: @\"\"@
--
cellViewBackground :: CellViewClass self => WriteAttr self String
cellViewBackground = writeAttrFromStringProperty "background"

#endif