File: RadioToolButton.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 (184 lines) | stat: -rw-r--r-- 6,216 bytes parent folder | download | duplicates (3)
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
{-# LANGUAGE CPP #-}
-- -*-haskell-*-
--  GIMP Toolkit (GTK) Widget RadioToolButton
--
--  Author : Duncan Coutts
--
--  Created: 7 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 toolbar item that contains a radio button
--
-- * Module available since Gtk+ version 2.4
--
module Graphics.UI.Gtk.MenuComboToolbar.RadioToolButton (
-- * Detail
-- 
-- | A 'RadioToolButton' is a 'ToolItem' that contains a radio button, that
-- is, a button that is part of a group of toggle buttons where only one button
-- can be active at a time.
--
-- Use 'radioToolButtonNew' to create a new 'RadioToolButton'. use
-- 'radioToolButtonNewFromWidget' to create a new 'RadioToolButton' that is
-- part of the same group as an existing 'RadioToolButton'. Use
-- 'radioToolButtonNewFromStock' or 'radioToolButtonNewWithStockFromWidget' to
-- create a new 'RadioToolButton' containing a stock item.

-- * Class Hierarchy
-- |
-- @
-- |  'GObject'
-- |   +----'Object'
-- |         +----'Widget'
-- |               +----'Container'
-- |                     +----'Bin'
-- |                           +----'ToolItem'
-- |                                 +----'ToolButton'
-- |                                       +----'ToggleToolButton'
-- |                                             +----RadioToolButton
-- @

#if GTK_CHECK_VERSION(2,4,0)
-- * Types
  RadioToolButton,
  RadioToolButtonClass,
  castToRadioToolButton, gTypeRadioToolButton,
  toRadioToolButton,

-- * Constructors
  radioToolButtonNew,
  radioToolButtonNewFromStock,
  radioToolButtonNewFromWidget,
  radioToolButtonNewWithStockFromWidget,

-- * Methods
  radioToolButtonGetGroup,
  radioToolButtonSetGroup,

-- * Attributes
  radioToolButtonGroup,
#endif
  ) where

import Control.Monad	(liftM)

import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GList
import System.Glib.Attributes
import Graphics.UI.Gtk.Abstract.Object	(makeNewObject)
{#import Graphics.UI.Gtk.Types#}
import Graphics.UI.Gtk.General.StockItems

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

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

-- | Creates a new 'RadioToolButton', creating a new group.
--
radioToolButtonNew :: IO RadioToolButton
radioToolButtonNew =
  makeNewObject mkRadioToolButton $
  liftM (castPtr :: Ptr ToolItem -> Ptr RadioToolButton) $
  {# call gtk_radio_tool_button_new #}
    nullPtr

-- | Creates a new 'RadioToolButton', creating a new group. The new
-- 'RadioToolButton' will contain an icon and label from the stock item
-- indicated by @stockId@.
--
radioToolButtonNewFromStock :: 
    StockId            -- ^ @stockId@ - the name of a stock item
 -> IO RadioToolButton
radioToolButtonNewFromStock stockId =
  makeNewObject mkRadioToolButton $
  liftM (castPtr :: Ptr ToolItem -> Ptr RadioToolButton) $
  withUTFString stockId $ \stockIdPtr ->
  {# call gtk_radio_tool_button_new_from_stock #}
    nullPtr
    stockIdPtr

-- | Creates a new 'RadioToolButton' adding it to the same group as 
-- the group to which @groupMember@ belongs.
--
radioToolButtonNewFromWidget :: RadioToolButtonClass groupMember => 
    groupMember        -- ^ @groupMember@ - a member of an existing radio group,
                       -- to which the new radio tool button will be added.
 -> IO RadioToolButton
radioToolButtonNewFromWidget group =
  makeNewObject mkRadioToolButton $
  liftM (castPtr :: Ptr ToolItem -> Ptr RadioToolButton) $
  {# call gtk_radio_tool_button_new_from_widget #}
    (toRadioToolButton group)

-- | Creates a new 'RadioToolButton' adding it to the same group as the group
-- to which @groupMember@ belongs. The new 'RadioToolButton' will contain an
-- icon and label from the stock item indicated by @stockId@.
--
radioToolButtonNewWithStockFromWidget :: RadioToolButtonClass groupMember => 
    groupMember        -- ^ @groupMember@ - a member of an existing radio group,
                       -- to which the new radio tool button will be added.
 -> StockId            -- ^ @stockId@ - the name of a stock item
 -> IO RadioToolButton
radioToolButtonNewWithStockFromWidget group stockId =
  makeNewObject mkRadioToolButton $
  liftM (castPtr :: Ptr ToolItem -> Ptr RadioToolButton) $
  withUTFString stockId $ \stockIdPtr ->
  {# call gtk_radio_tool_button_new_with_stock_from_widget #}
    (toRadioToolButton group)
    stockIdPtr

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

-- | Returns the radio button group @button@ belongs to.
--
radioToolButtonGetGroup :: RadioToolButtonClass self => self
 -> IO [RadioToolButton] -- ^ returns the group the button belongs to.
radioToolButtonGetGroup self =
  {# call unsafe gtk_radio_tool_button_get_group #}
    (toRadioToolButton self)
  >>= readGSList
  >>= mapM (\elemPtr -> makeNewObject mkRadioToolButton (return elemPtr))

-- | Adds @button@ to @group@, removing it from the group it belonged to
-- before.
--
radioToolButtonSetGroup :: RadioToolButtonClass self => self
 -> RadioToolButton -- ^ @groupMember@ - a member of an existing radio group,
                    -- to which the radio tool button will be added.
 -> IO ()
radioToolButtonSetGroup self group =
  {# call unsafe gtk_radio_tool_button_get_group #} group >>= \groupGSList ->
  {# call gtk_radio_tool_button_set_group #}
    (toRadioToolButton self)
    groupGSList

--------------------
-- Properties

-- | Sets a new group for a radio tool button.
--
radioToolButtonGroup :: RadioToolButtonClass self => ReadWriteAttr self [RadioToolButton] RadioToolButton
radioToolButtonGroup = newAttr
  radioToolButtonGetGroup
  radioToolButtonSetGroup
#endif