1{-# LANGUAGE CPP #-}
2-- -*-haskell-*-
3--  GIMP Toolkit (GTK) Widget Container
4--
5--  Author : Axel Simon
6--
7--  Created: 15 May 2001
8--
9--  Copyright (C) 1999-2005 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-- Base class for widgets which contain other widgets
27--
28module Graphics.UI.Gtk.Abstract.Container (
29-- * Detail
30--
31-- | A Gtk+ user interface is constructed by nesting widgets inside widgets.
32-- Container widgets are the inner nodes in the resulting tree of widgets: they
33-- contain other widgets. So, for example, you might have a 'Window' containing
34-- a 'Frame' containing a 'Label'. If you wanted an image instead of a textual
35-- label inside the frame, you might replace the 'Label' widget with a 'Image'
36-- widget.
37--
38-- There are two major kinds of container widgets in Gtk+. Both are
39-- subclasses of the abstract 'Container' base class.
40--
41-- The first type of container widget has a single child widget and derives
42-- from 'Bin'. These containers are decorators, which add some kind of
43-- functionality to the child. For example, a 'Button' makes its child into a
44-- clickable button; a 'Frame' draws a frame around its child and a 'Window'
45-- places its child widget inside a top-level window.
46--
47-- The second type of container can have more than one child; its purpose is
48-- to manage layout. This means that these containers assign sizes and
49-- positions to their children. For example, a 'HBox' arranges its children in
50-- a horizontal row, and a 'Table' arranges the widgets it contains in a
51-- two-dimensional grid.
52--
53-- To fulfill its task, a layout container must negotiate the size
54-- requirements with its parent and its children. This negotiation is carried
55-- out in two phases, size requisition and size allocation.
56
57-- ** Size Requisition
58--
59-- | The size requisition of a widget is it's desired width and height. This
60-- is represented by a 'Requisition'.
61--
62-- How a widget determines its desired size depends on the widget. A
63-- 'Label', for example, requests enough space to display all its text.
64-- Container widgets generally base their size request on the requisitions of
65-- their children.
66--
67-- The size requisition phase of the widget layout process operates
68-- top-down. It starts at a top-level widget, typically a 'Window'. The
69-- top-level widget asks its child for its size requisition by calling
70-- 'widgetSizeRequest'. To determine its requisition, the child asks its own
71-- children for their requisitions and so on. Finally, the top-level widget
72-- will get a requisition back from its child.
73
74-- ** Size Allocation
75--
76-- | When the top-level widget has determined how much space its child would
77-- like to have, the second phase of the size negotiation, size allocation,
78-- begins. Depending on its configuration (see 'windowSetResizable'), the
79-- top-level widget may be able to expand in order to satisfy the size request
80-- or it may have to ignore the size request and keep its fixed size. It then
81-- tells its child widget how much space it gets by calling
82-- 'widgetSizeAllocate'. The child widget divides the space among its children
83-- and tells each child how much space it got, and so on. Under normal
84-- circumstances, a 'Window' will always give its child the amount of space the
85-- child requested.
86--
87-- A child's size allocation is represented by an 'Allocation'.
88-- This contains not only a width and height, but also a
89-- position (i.e. X and Y coordinates), so that containers can tell their
90-- children not only how much space they have gotten, but also where they are
91-- positioned inside the space available to the container.
92--
93-- Widgets are required to honor the size allocation they receive; a size
94-- request is only a request, and widgets must be able to cope with any size.
95
96-- ** Child attributes
97--
98-- | 'Container' introduces child attributes - these are object attributes
99-- that are not specific to either the container or the contained widget, but
100-- rather to their relation. Typical examples of child attributes are the
101-- position or pack-type of a widget which is contained in a 'Box'.
102--
103-- The 'Container' class does not itself define any child attributes, they are
104-- defined (and documented) by the various 'Container' subclasses.
105--
106-- Child attributes can be set or obtained in a similar way to ordinary
107-- attributes. So ordinary attributes are set like so:
108--
109-- > set object [ attr := value ]
110--
111-- Whereas child attributes take the child object as a parameter:
112--
113-- > set container [ attr child := value ]
114--
115-- And similarily for getting a child attribute's value:
116--
117-- > value <- get container (attr child)
118--
119
120-- * Class Hierarchy
121-- |
122-- @
123-- |  'GObject'
124-- |   +----'Object'
125-- |         +----'Widget'
126-- |               +----Container
127-- |                     +----'Bin'
128-- |                     +----'Box'
129-- |                     +----'CList'
130-- |                     +----'Fixed'
131-- |                     +----'Paned'
132-- |                     +----'IconView'
133-- |                     +----'Layout'
134-- |                     +----'List'
135-- |                     +----'MenuShell'
136-- |                     +----'Notebook'
137-- |                     +----'Socket'
138-- |                     +----'Table'
139-- |                     +----'TextView'
140-- |                     +----'Toolbar'
141-- |                     +----'TreeView'
142-- @
143
144-- * Types
145  Container,
146  ContainerClass,
147  castToContainer, gTypeContainer,
148  toContainer,
149  ContainerForeachCB,
150  ResizeMode(..),
151
152-- * Methods
153  containerAdd,
154  containerRemove,
155  containerForeach,
156  containerForall,
157  containerGetChildren,
158  containerSetFocusChild,
159  containerSetFocusChain,
160  containerGetFocusChain,
161  containerUnsetFocusChain,
162  containerSetFocusVAdjustment,
163  containerGetFocusVAdjustment,
164  containerSetFocusHAdjustment,
165  containerGetFocusHAdjustment,
166  containerResizeChildren,
167  containerSetBorderWidth,
168  containerGetBorderWidth,
169  containerGetResizeMode,
170  containerSetResizeMode,
171
172-- * Attributes
173  containerResizeMode,
174  containerBorderWidth,
175  containerChild,
176  containerFocusHAdjustment,
177  containerFocusVAdjustment,
178
179-- * Signals
180  add,
181  checkResize,
182  remove,
183  setFocusChild,
184
185-- * Deprecated
186#ifndef DISABLE_DEPRECATED
187  onAdd,
188  afterAdd,
189  onCheckResize,
190  afterCheckResize,
191  onRemove,
192  afterRemove,
193  onSetFocusChild,
194  afterSetFocusChild,
195#endif
196  ) where
197
198import Control.Monad    (liftM)
199
200import System.Glib.FFI
201import System.Glib.Attributes
202import System.Glib.Properties
203import Graphics.UI.Gtk.Abstract.Object  (makeNewObject)
204{#import Graphics.UI.Gtk.Types#}
205{#import Graphics.UI.Gtk.Signals#}
206import System.Glib.GList                (fromGList, withGList)
207import Graphics.UI.Gtk.General.Enums    (ResizeMode(..))
208
209{# context lib="gtk" prefix="gtk" #}
210
211--------------------
212-- Methods
213
214-- | Adds @widget@ to the container. Typically used for simple containers such
215-- as 'Window', 'Frame', or 'Button'; for more complicated layout containers
216-- such as 'Box' or 'Table', this function will pick default packing parameters
217-- that may not be correct. So consider functions such as 'boxPackStart' and
218-- 'tableAttach' as an alternative to 'containerAdd' in those cases. A widget
219-- may be added to only one container at a time; you can't place the same
220-- widget inside two different containers.
221--
222containerAdd :: (ContainerClass self, WidgetClass widget) => self
223 -> widget -- ^ @widget@ - a widget to be placed inside @container@
224 -> IO ()
225containerAdd self widget =
226  {# call container_add #}
227    (toContainer self)
228    (toWidget widget)
229
230-- | Removes @widget@ from @container@. @widget@ must be inside @container@.
231--
232containerRemove :: (ContainerClass self, WidgetClass widget) => self
233 -> widget -- ^ @widget@ - a current child of @container@
234 -> IO ()
235containerRemove self widget =
236  {# call container_remove #}
237    (toContainer self)
238    (toWidget widget)
239
240-- | Maps @callback@ over each non-internal child of @container@. See
241-- 'containerForall' for details on what constitutes an \"internal\" child.
242-- Most applications should use 'containerForeach', rather than
243-- 'containerForall'.
244--
245containerForeach :: ContainerClass self => self
246 -> ContainerForeachCB
247 -> IO ()
248containerForeach self fun = do
249  fPtr <- mkContainerForeachFunc (\wPtr _ -> do
250    w <- makeNewObject mkWidget (return wPtr)
251    fun w)
252  {# call container_foreach #}
253    (toContainer self)
254    fPtr
255    nullPtr
256  freeHaskellFunPtr fPtr
257
258-- | A function that is invoked for all widgets in a container.
259type ContainerForeachCB = Widget -> IO ()
260{#pointer Callback#}
261
262foreign import ccall "wrapper" mkContainerForeachFunc ::
263  (Ptr Widget -> Ptr () -> IO ()) -> IO Callback
264
265-- | Maps @callback@ over each child of @container@, including children that
266-- are considered \"internal\" (implementation details of the container).
267-- \"Internal\" children generally weren't added by the user of the container,
268-- but were added by the container implementation itself. Most applications
269-- should use 'containerForeach', rather than 'containerForall'.
270--
271containerForall :: ContainerClass self => self
272 -> ContainerForeachCB -- ^ @callback@ - a callback
273 -> IO ()
274containerForall self fun = do
275  fPtr <- mkContainerForeachFunc (\wPtr _ -> do
276    w <- makeNewObject mkWidget (return wPtr)
277    fun w)
278  {# call container_forall #}
279    (toContainer self)
280    fPtr
281    nullPtr
282  freeHaskellFunPtr fPtr
283
284-- | Returns the container's non-internal children. See 'containerForall' for
285-- details on what constitutes an \"internal\" child.
286--
287containerGetChildren :: ContainerClass self => self
288 -> IO [Widget]
289containerGetChildren self = do
290  glist <- {# call container_get_children #} (toContainer self)
291  widgetPtrs <- fromGList glist
292  mapM (makeNewObject mkWidget . return) widgetPtrs
293
294-- | Give the focus to a specific child of the container.
295--
296containerSetFocusChild :: (ContainerClass self, WidgetClass child) => self
297 -> child -- ^ @child@
298 -> IO ()
299containerSetFocusChild self child =
300  {# call container_set_focus_child #}
301    (toContainer self)
302    (toWidget child)
303
304-- | Sets a focus chain, overriding the one computed automatically by Gtk+.
305--
306-- In principle each widget in the chain should be a descendant of the
307-- container, but this is not enforced by this method, since it's allowed to
308-- set the focus chain before you pack the widgets, or have a widget in the
309-- chain that isn't always packed. The necessary checks are done when the focus
310-- chain is actually traversed.
311--
312containerSetFocusChain :: ContainerClass self => self
313 -> [Widget] -- ^ @focusableWidgets@ - the new focus chain.
314 -> IO ()
315containerSetFocusChain self chain =
316  withForeignPtrs (map unWidget chain) $ \wPtrs ->
317  withGList wPtrs $ \glist ->
318  {# call container_set_focus_chain #}
319    (toContainer self)
320    glist
321
322-- | Retrieves the focus chain of the container, if one has been set
323-- explicitly. If no focus chain has been explicitly set, Gtk+ computes the
324-- focus chain based on the positions of the children. In that case the
325-- function returns @Nothing@.
326--
327containerGetFocusChain :: ContainerClass self => self
328 -> IO (Maybe [Widget])
329containerGetFocusChain self =
330  alloca $ \glistPtr -> do
331  {# call container_get_focus_chain #}
332    (toContainer self)
333    glistPtr
334  if glistPtr == nullPtr then return Nothing else liftM Just $ do
335    glist <- peek glistPtr
336    widgetPtrs <- fromGList glist
337    mapM (makeNewObject mkWidget . return) widgetPtrs
338
339-- | Removes a focus chain explicitly set with 'containerSetFocusChain'.
340--
341containerUnsetFocusChain :: ContainerClass self => self -> IO ()
342containerUnsetFocusChain self =
343  {# call container_unset_focus_chain #}
344    (toContainer self)
345
346-- | Hooks up an adjustment to focus handling in a container, so when a child
347-- of the container is focused, the adjustment is scrolled to show that widget.
348-- This function sets the vertical alignment. See
349-- 'scrolledWindowGetVAdjustment' for a typical way of obtaining the adjustment
350-- and 'containerSetFocusHAdjustment' for setting the horizontal adjustment.
351--
352-- The adjustments have to be in pixel units and in the same coordinate
353-- system as the allocation for immediate children of the container.
354--
355containerSetFocusVAdjustment :: ContainerClass self => self
356 -> Adjustment -- ^ @adjustment@ - an adjustment which should be adjusted when
357               -- the focus is moved among the descendents of @container@
358 -> IO ()
359containerSetFocusVAdjustment self adjustment =
360  {# call container_set_focus_vadjustment #}
361    (toContainer self)
362    adjustment
363
364-- | Retrieves the vertical focus adjustment for the container. See
365-- 'containerSetFocusVAdjustment'.
366--
367containerGetFocusVAdjustment :: ContainerClass self => self
368 -> IO (Maybe Adjustment) -- ^ returns the vertical focus adjustment, or
369                          -- @Nothing@ if none has been set.
370containerGetFocusVAdjustment self =
371  maybeNull (makeNewObject mkAdjustment) $
372  {# call unsafe container_get_focus_vadjustment #}
373    (toContainer self)
374
375-- | Hooks up an adjustment to focus handling in a container, so when a child
376-- of the container is focused, the adjustment is scrolled to show that widget.
377-- This function sets the horizontal alignment. See
378-- 'scrolledWindowGetHAdjustment' for a typical way of obtaining the adjustment
379-- and 'containerSetFocusVAdjustment' for setting the vertical adjustment.
380--
381-- The adjustments have to be in pixel units and in the same coordinate
382-- system as the allocation for immediate children of the container.
383--
384containerSetFocusHAdjustment :: ContainerClass self => self
385 -> Adjustment -- ^ @adjustment@ - an adjustment which should be adjusted when
386               -- the focus is moved among the descendents of @container@
387 -> IO ()
388containerSetFocusHAdjustment self adjustment =
389  {# call container_set_focus_hadjustment #}
390    (toContainer self)
391    adjustment
392
393-- | Retrieves the horizontal focus adjustment for the container. See
394-- 'containerSetFocusHAdjustment'.
395--
396containerGetFocusHAdjustment :: ContainerClass self => self
397 -> IO (Maybe Adjustment) -- ^ returns the horizontal focus adjustment, or
398                          -- @Nothing@ if none has been set.
399containerGetFocusHAdjustment self =
400  maybeNull (makeNewObject mkAdjustment) $
401  {# call unsafe container_get_focus_hadjustment #}
402    (toContainer self)
403
404-- | Make the container resize its children.
405--
406containerResizeChildren :: ContainerClass self => self -> IO ()
407containerResizeChildren self =
408  {# call container_resize_children #}
409    (toContainer self)
410
411-- | Sets the border width of the container.
412--
413-- The border width of a container is the amount of space to leave around
414-- the outside of the container. The only exception to this is 'Window';
415-- because toplevel windows can't leave space outside, they leave the space
416-- inside. The border is added on all sides of the container. To add space to
417-- only one side, one approach is to create a 'Alignment' widget, call
418-- 'widgetSetUsize' to give it a size, and place it on the side of the
419-- container as a spacer.
420--
421containerSetBorderWidth :: ContainerClass self => self
422 -> Int   -- ^ @borderWidth@ - amount of blank space to leave /outside/ the
423          -- container. Valid values are in the range 0-65535 pixels.
424 -> IO ()
425containerSetBorderWidth self borderWidth =
426  {# call container_set_border_width #}
427    (toContainer self)
428    (fromIntegral borderWidth)
429
430-- | Retrieves the border width of the container. See
431-- 'containerSetBorderWidth'.
432--
433containerGetBorderWidth :: ContainerClass self => self
434 -> IO Int -- ^ returns the current border width
435containerGetBorderWidth self =
436  liftM fromIntegral $
437  {# call unsafe container_get_border_width #}
438    (toContainer self)
439
440-- | Returns the resize mode for the container. See 'containerSetResizeMode'.
441--
442containerGetResizeMode :: ContainerClass self => self
443 -> IO ResizeMode -- ^ returns the current resize mode
444containerGetResizeMode self =
445  liftM (toEnum . fromIntegral) $
446  {# call gtk_container_get_resize_mode #}
447    (toContainer self)
448
449-- | Sets the resize mode for the container.
450--
451-- The resize mode of a container determines whether a resize request will
452-- be passed to the container's parent, queued for later execution or executed
453-- immediately.
454--
455containerSetResizeMode :: ContainerClass self => self
456 -> ResizeMode -- ^ @resizeMode@ - the new resize mode.
457 -> IO ()
458containerSetResizeMode self resizeMode =
459  {# call gtk_container_set_resize_mode #}
460    (toContainer self)
461    ((fromIntegral . fromEnum) resizeMode)
462
463--------------------
464-- Attributes
465
466-- | Specify how resize events are handled.
467--
468-- Default value: 'ResizeParent'
469--
470containerResizeMode :: ContainerClass self => Attr self ResizeMode
471containerResizeMode = newAttr
472  containerGetResizeMode
473  containerSetResizeMode
474
475-- | The width of the empty border outside the containers children.
476--
477-- Allowed values: \<= @('maxBound' :: Int)@
478--
479-- Default value: 0
480--
481containerBorderWidth :: ContainerClass self => Attr self Int
482containerBorderWidth = newAttr
483  containerGetBorderWidth
484  containerSetBorderWidth
485
486-- | Can be used to add a new child to the container.
487--
488containerChild :: (ContainerClass self, WidgetClass widget) => WriteAttr self widget
489containerChild = writeAttrFromObjectProperty "child"
490  {# call pure unsafe gtk_widget_get_type #}
491
492-- | \'focusHadjustment\' property. See 'containerGetFocusHAdjustment' and
493-- 'containerSetFocusHAdjustment'
494--
495containerFocusHAdjustment :: ContainerClass self => ReadWriteAttr self (Maybe Adjustment) Adjustment
496containerFocusHAdjustment = newAttr
497  containerGetFocusHAdjustment
498  containerSetFocusHAdjustment
499
500-- | \'focusVadjustment\' property. See 'containerGetFocusVAdjustment' and
501-- 'containerSetFocusVAdjustment'
502--
503containerFocusVAdjustment :: ContainerClass self => ReadWriteAttr self (Maybe Adjustment) Adjustment
504containerFocusVAdjustment = newAttr
505  containerGetFocusVAdjustment
506  containerSetFocusVAdjustment
507
508--------------------
509-- Signals
510
511-- %hash c:26b d:af3f
512-- | A widget was added to the container.
513--
514add :: ContainerClass self => Signal self (Widget -> IO ())
515add = Signal (connect_OBJECT__NONE "add")
516
517-- %hash c:f43a d:af3f
518-- | A widget was removed from the container.
519--
520remove :: ContainerClass self => Signal self (Widget -> IO ())
521remove = Signal (connect_OBJECT__NONE "remove")
522
523-- %hash c:21a9 d:af3f
524-- | Emitted when widgets need to be queried again for their preferred size.
525--
526checkResize :: ContainerClass self => Signal self (IO ())
527checkResize = Signal (connect_NONE__NONE "check-resize")
528
529-- %hash c:b3a d:af3f
530-- | A widget in the container received or lost the input focus.
531--
532setFocusChild :: ContainerClass self => Signal self (Maybe Widget -> IO ())
533setFocusChild = Signal (connect_MOBJECT__NONE "set-focus-child")
534
535--------------------
536-- Deprecated Signals
537
538#ifndef DISABLE_DEPRECATED
539-- %hash c:fb37
540onAdd :: ContainerClass self => self
541 -> (Widget -> IO ())
542 -> IO (ConnectId self)
543onAdd = connect_OBJECT__NONE "add" False
544{-# DEPRECATED onAdd "instead of 'onAdd obj' use 'on obj add'" #-}
545
546-- %hash c:c9d6
547afterAdd :: ContainerClass self => self
548 -> (Widget -> IO ())
549 -> IO (ConnectId self)
550afterAdd = connect_OBJECT__NONE "add" True
551{-# DEPRECATED afterAdd "instead of 'afterAdd obj' use 'after obj add'" #-}
552
553-- %hash c:9b66
554onRemove :: ContainerClass self => self
555 -> (Widget -> IO ())
556 -> IO (ConnectId self)
557onRemove = connect_OBJECT__NONE "remove" False
558{-# DEPRECATED onRemove "instead of 'onRemove obj' use 'on obj remove'" #-}
559
560-- %hash c:f165
561afterRemove :: ContainerClass self => self
562 -> (Widget -> IO ())
563 -> IO (ConnectId self)
564afterRemove = connect_OBJECT__NONE "remove" True
565{-# DEPRECATED afterRemove "instead of 'afterRemove obj' use 'after obj remove'" #-}
566
567-- %hash c:8424
568onCheckResize :: ContainerClass self => self
569 -> IO ()
570 -> IO (ConnectId self)
571onCheckResize = connect_NONE__NONE "check_resize" False
572{-# DEPRECATED onCheckResize "instead of 'onCheckResize obj' use 'on obj checkResize'" #-}
573
574-- %hash c:6803
575afterCheckResize :: ContainerClass self => self
576 -> IO ()
577 -> IO (ConnectId self)
578afterCheckResize = connect_NONE__NONE "check_resize" True
579{-# DEPRECATED afterCheckResize "instead of 'afterCheckResize obj' use 'after obj checkResize'" #-}
580
581-- %hash c:1ac6
582onSetFocusChild :: ContainerClass self => self
583 -> (Maybe Widget -> IO ())
584 -> IO (ConnectId self)
585onSetFocusChild = connect_MOBJECT__NONE "set-focus-child" False
586{-# DEPRECATED onSetFocusChild "instead of 'onSetFocusChild obj' use 'on obj setFocusChild'" #-}
587
588-- %hash c:23e5
589afterSetFocusChild :: ContainerClass self => self
590 -> (Maybe Widget -> IO ())
591 -> IO (ConnectId self)
592afterSetFocusChild = connect_MOBJECT__NONE "set-focus-child" True
593{-# DEPRECATED afterSetFocusChild "instead of 'afterSetFocusChild obj' use 'after obj setFocusChild'" #-}
594#endif
595