File: ScrolledWindow.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 (364 lines) | stat: -rw-r--r-- 13,781 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
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
{-# LANGUAGE CPP #-}
-- -*-haskell-*-
--  GIMP Toolkit (GTK) Widget ScrolledWindow
--
--  Author : Axel Simon
--
--  Created: 23 May 2001
--
--  Copyright (C) 1999-2005 Axel Simon
--
--  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)
--
-- Adds scrollbars to its child widget
--
module Graphics.UI.Gtk.Scrolling.ScrolledWindow (
-- * Detail
-- 
-- | 'ScrolledWindow' is a 'Bin' subclass: it's a container the accepts a
-- single child widget. 'ScrolledWindow' adds scrollbars to the child widget
-- and optionally draws a beveled frame around the child widget.
--
-- The scrolled window can work in two ways. Some widgets have native
-- scrolling support; these widgets have \"slots\" for 'Adjustment' objects.
-- Widgets with native scroll support include 'TreeView', 'TextView', and
-- 'Layout'.
--
-- For widgets that lack native scrolling support, the 'Viewport' widget
-- acts as an adaptor class, implementing scrollability for child widgets that
-- lack their own scrolling capabilities. Use 'Viewport' to scroll child
-- widgets such as 'Table', 'Box', and so on.
--
-- If a widget has native scrolling abilities, it can be added to the
-- 'ScrolledWindow' with 'Graphics.UI.Gtk.Abstract.Container.containerAdd'.
-- If a widget does not, you must first add the widget to a 'Viewport', then
-- add the 'Viewport' to the scrolled window. The convenience function
-- 'scrolledWindowAddWithViewport' does exactly this, so you can ignore the
-- presence of the viewport.
--
-- The position of the scrollbars is controlled by the scroll adjustments.
-- See 'Adjustment' for the fields in an adjustment - for 'Scrollbar', used by
-- 'ScrolledWindow', the \"value\" field represents the position of the
-- scrollbar, which must be between the \"lower\" field and \"upper -
-- page_size.\" The \"page_size\" field represents the size of the visible
-- scrollable area. The \"step_increment\" and \"page_increment\" fields are
-- used when the user asks to step down (using the small stepper arrows) or
-- page down (using for example the PageDown key).
--
-- If a 'ScrolledWindow' doesn't behave quite as you would like, or doesn't
-- have exactly the right layout, it's very possible to set up your own
-- scrolling with 'Scrollbar' and for example a 'Table'.

-- * Class Hierarchy
-- |
-- @
-- |  'GObject'
-- |   +----'Object'
-- |         +----'Widget'
-- |               +----'Container'
-- |                     +----'Bin'
-- |                           +----ScrolledWindow
-- @

-- * Types
  ScrolledWindow,
  ScrolledWindowClass,
  castToScrolledWindow, gTypeScrolledWindow,
  toScrolledWindow,

-- * Constructors
  scrolledWindowNew,

-- * Methods
  scrolledWindowGetHAdjustment,
  scrolledWindowGetVAdjustment,
  PolicyType(..),
  scrolledWindowSetPolicy,
  scrolledWindowGetPolicy,
  scrolledWindowAddWithViewport,
  CornerType(..),
  scrolledWindowSetPlacement,
  scrolledWindowGetPlacement,
  ShadowType(..),
  scrolledWindowSetShadowType,
  scrolledWindowGetShadowType,
  scrolledWindowSetHAdjustment,
  scrolledWindowSetVAdjustment,
#if GTK_CHECK_VERSION(2,8,0)
  scrolledWindowGetHScrollbar,
  scrolledWindowGetVScrollbar,
#endif

-- * Attributes
  scrolledWindowHAdjustment,
  scrolledWindowVAdjustment,
  scrolledWindowHscrollbarPolicy,
  scrolledWindowVscrollbarPolicy,
  scrolledWindowWindowPlacement,
  scrolledWindowShadowType,
  scrolledWindowPlacement,
  ) where

import Control.Monad	(liftM)
import Data.Maybe    (fromMaybe)

import System.Glib.FFI
import System.Glib.Attributes
import System.Glib.Properties
import Graphics.UI.Gtk.Abstract.Object	(makeNewObject)
{#import Graphics.UI.Gtk.Types#}
import Graphics.UI.Gtk.General.Enums	(PolicyType(..), CornerType(..), ShadowType(..))

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

--------------------
-- Constructors

-- | Creates a new scrolled window. The two arguments are the scrolled
-- window's adjustments; these will be shared with the scrollbars and the child
-- widget to keep the bars in sync with the child. Usually you want to pass
-- @Nothing@ for the adjustments, which will cause the scrolled window to
-- create them for you.
--
scrolledWindowNew :: 
    Maybe Adjustment  -- ^ @hadjustment@ - Horizontal adjustment.
 -> Maybe Adjustment  -- ^ @vadjustment@ - Vertical adjustment.
 -> IO ScrolledWindow
scrolledWindowNew hadjustment vadjustment =
  makeNewObject mkScrolledWindow $
  liftM (castPtr :: Ptr Widget -> Ptr ScrolledWindow) $
  {# call unsafe scrolled_window_new #}
    (fromMaybe (Adjustment nullForeignPtr) hadjustment)
    (fromMaybe (Adjustment nullForeignPtr) vadjustment)

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

-- | Returns the horizontal scrollbar's adjustment, used to connect the
-- horizontal scrollbar to the child widget's horizontal scroll functionality.
--
scrolledWindowGetHAdjustment :: ScrolledWindowClass self => self -> IO Adjustment
scrolledWindowGetHAdjustment self =
  makeNewObject mkAdjustment $
  {# call unsafe scrolled_window_get_hadjustment #}
    (toScrolledWindow self)

-- | Returns the vertical scrollbar's adjustment, used to connect the vertical
-- scrollbar to the child widget's vertical scroll functionality.
--
scrolledWindowGetVAdjustment :: ScrolledWindowClass self => self -> IO Adjustment
scrolledWindowGetVAdjustment self =
  makeNewObject mkAdjustment $
  {# call unsafe scrolled_window_get_vadjustment #}
    (toScrolledWindow self)

-- | Sets the scrollbar policy for the horizontal and vertical scrollbars. The
-- policy determines when the scrollbar should appear; it is a value from the
-- 'PolicyType' enumeration. If 'PolicyAlways', the scrollbar is always
-- present; if 'PolicyNever', the scrollbar is never present; if
-- 'PolicyAutomatic', the scrollbar is present only if needed (that is, if the
-- slider part of the bar would be smaller than the trough - the display is
-- larger than the page size).
--
scrolledWindowSetPolicy :: ScrolledWindowClass self => self
 -> PolicyType -- ^ @hscrollbarPolicy@ - Policy for horizontal bar.
 -> PolicyType -- ^ @vscrollbarPolicy@ - Policy for vertical bar.
 -> IO ()
scrolledWindowSetPolicy self hscrollbarPolicy vscrollbarPolicy =
  {# call scrolled_window_set_policy #}
    (toScrolledWindow self)
    ((fromIntegral . fromEnum) hscrollbarPolicy)
    ((fromIntegral . fromEnum) vscrollbarPolicy)

-- | Retrieves the current policy values for the horizontal and vertical
-- scrollbars. See 'scrolledWindowSetPolicy'.
--
scrolledWindowGetPolicy :: ScrolledWindowClass self => self
 -> IO (PolicyType, PolicyType) -- ^ @(hscrollbarPolicy, vscrollbarPolicy)@
scrolledWindowGetPolicy self =
  alloca $ \hPolPtr ->
  alloca $ \vPolPtr -> do
  {# call unsafe scrolled_window_get_policy #}
    (toScrolledWindow self)
    hPolPtr vPolPtr
  hPol <- liftM (toEnum.fromIntegral) $ peek hPolPtr
  vPol <- liftM (toEnum.fromIntegral) $ peek vPolPtr
  return (hPol, vPol)

-- | Used to add children without native scrolling capabilities. This is
-- simply a convenience function; it is equivalent to adding the unscrollable
-- child to a viewport, then adding the viewport to the scrolled window. If a
-- child has native scrolling, use
-- 'Graphics.UI.Gtk.Abstract.Container.containerAdd' instead of this function.
--
-- The viewport scrolls the child by moving its 'DrawWindow', and takes the
-- size of the child to be the size of its toplevel 'DrawWindow'. This will be
-- very wrong for most widgets that support native scrolling; for example, if
-- you add a widget such as 'TreeView' with a viewport, the whole widget will
-- scroll, including the column headings. Thus, widgets with native scrolling
-- support should not be used with the 'Viewport' proxy.
--
scrolledWindowAddWithViewport :: (ScrolledWindowClass self, WidgetClass child) => self
 -> child -- ^ @child@ - Widget you want to scroll.
 -> IO ()
scrolledWindowAddWithViewport self child =
  {# call scrolled_window_add_with_viewport #}
    (toScrolledWindow self)
    (toWidget child)

-- | Determines the location of the child widget with respect to the
-- scrollbars. The default is 'CornerTopLeft', meaning the child is in the top
-- left, with the scrollbars underneath and to the right. Other values in
-- 'CornerType' are 'CornerTopRight', 'CornerBottomLeft', and
-- 'CornerBottomRight'.
--
scrolledWindowSetPlacement :: ScrolledWindowClass self => self
 -> CornerType -- ^ @windowPlacement@ - Position of the child window.
 -> IO ()
scrolledWindowSetPlacement self windowPlacement =
  {# call scrolled_window_set_placement #}
    (toScrolledWindow self)
    ((fromIntegral . fromEnum) windowPlacement)

-- | Gets the placement of the scrollbars for the scrolled window. See
-- 'scrolledWindowSetPlacement'.
--
scrolledWindowGetPlacement :: ScrolledWindowClass self => self -> IO CornerType
scrolledWindowGetPlacement self =
  liftM (toEnum . fromIntegral) $
  {# call unsafe scrolled_window_get_placement #}
    (toScrolledWindow self)

-- | Changes the type of shadow drawn around the contents of @scrolledWindow@.
--
scrolledWindowSetShadowType :: ScrolledWindowClass self => self -> ShadowType -> IO ()
scrolledWindowSetShadowType self type_ =
  {# call scrolled_window_set_shadow_type #}
    (toScrolledWindow self)
    ((fromIntegral . fromEnum) type_)

-- | Gets the shadow type of the scrolled window. See
-- 'scrolledWindowSetShadowType'.
--
scrolledWindowGetShadowType :: ScrolledWindowClass self => self -> IO ShadowType
scrolledWindowGetShadowType self =
  liftM (toEnum . fromIntegral) $
  {# call unsafe scrolled_window_get_shadow_type #}
    (toScrolledWindow self)

-- | Sets the 'Adjustment' for the horizontal scrollbar.
--
scrolledWindowSetHAdjustment :: ScrolledWindowClass self => self -> Adjustment -> IO ()
scrolledWindowSetHAdjustment self hadjustment =
  {# call scrolled_window_set_hadjustment #}
    (toScrolledWindow self)
    hadjustment

-- | Sets the 'Adjustment' for the vertical scrollbar.
--
scrolledWindowSetVAdjustment :: ScrolledWindowClass self => self
 -> Adjustment -- ^ @vadjustment@ - Vertical scroll adjustment.
 -> IO ()
scrolledWindowSetVAdjustment self vadjustment =
  {# call scrolled_window_set_vadjustment #}
    (toScrolledWindow self)
    vadjustment

#if GTK_CHECK_VERSION(2,8,0)
-- | Returns the horizontal scrollbar of @scrolledWindow@.
--
-- * Available since Gtk+ version 2.8
--
scrolledWindowGetHScrollbar :: ScrolledWindowClass self => self
 -> IO (Maybe HScrollbar) -- ^ returns the horizontal scrollbar of the scrolled
                          -- window, or @Nothing@ if it does not have one.
scrolledWindowGetHScrollbar self =
  maybeNull (makeNewObject mkHScrollbar) $
  liftM (castPtr :: Ptr Widget -> Ptr HScrollbar) $
  {# call gtk_scrolled_window_get_hscrollbar #}
    (toScrolledWindow self)

-- | Returns the vertical scrollbar of @scrolledWindow@.
--
-- * Available since Gtk+ version 2.8
--
scrolledWindowGetVScrollbar :: ScrolledWindowClass self => self
 -> IO (Maybe VScrollbar) -- ^ returns the vertical scrollbar of the scrolled
                          -- window, or @Nothing@ if it does not have one.
scrolledWindowGetVScrollbar self =
  maybeNull (makeNewObject mkVScrollbar) $
  liftM (castPtr :: Ptr Widget -> Ptr VScrollbar) $
  {# call gtk_scrolled_window_get_vscrollbar #}
    (toScrolledWindow self)
#endif

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

-- | The 'Adjustment' for the horizontal position.
--
scrolledWindowHAdjustment :: ScrolledWindowClass self => Attr self Adjustment
scrolledWindowHAdjustment = newAttr
  scrolledWindowGetHAdjustment
  scrolledWindowSetHAdjustment

-- | The 'Adjustment' for the vertical position.
--
scrolledWindowVAdjustment :: ScrolledWindowClass self => Attr self Adjustment
scrolledWindowVAdjustment = newAttr
  scrolledWindowGetVAdjustment
  scrolledWindowSetVAdjustment

-- | When the horizontal scrollbar is displayed.
--
-- Default value: 'PolicyAlways'
--
scrolledWindowHscrollbarPolicy :: ScrolledWindowClass self => Attr self PolicyType
scrolledWindowHscrollbarPolicy = newAttrFromEnumProperty "hscrollbar-policy"
  {# call pure unsafe gtk_policy_type_get_type #}

-- | When the vertical scrollbar is displayed.
--
-- Default value: 'PolicyAlways'
--
scrolledWindowVscrollbarPolicy :: ScrolledWindowClass self => Attr self PolicyType
scrolledWindowVscrollbarPolicy = newAttrFromEnumProperty "vscrollbar-policy"
  {# call pure unsafe gtk_policy_type_get_type #}

-- | Where the contents are located with respect to the scrollbars.
--
-- Default value: 'CornerTopLeft'
--
scrolledWindowWindowPlacement :: ScrolledWindowClass self => Attr self CornerType
scrolledWindowWindowPlacement = newAttrFromEnumProperty "window-placement"
  {# call pure unsafe gtk_corner_type_get_type #}

-- | Style of bevel around the contents.
--
-- Default value: 'ShadowNone'
--
scrolledWindowShadowType :: ScrolledWindowClass self => Attr self ShadowType
scrolledWindowShadowType = newAttr
  scrolledWindowGetShadowType
  scrolledWindowSetShadowType

-- | \'placement\' property. See 'scrolledWindowGetPlacement' and
-- 'scrolledWindowSetPlacement'
--
scrolledWindowPlacement :: ScrolledWindowClass self => Attr self CornerType
scrolledWindowPlacement = newAttr
  scrolledWindowGetPlacement
  scrolledWindowSetPlacement