~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/wx/examples/demo/ex_button.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
 
 
19
%% This is example of the widgets and usage of wxErlang
 
20
%% Hopefully it will contain all implemented widgets, it's event handling
 
21
%% and some tutorials of how to use sizers and other stuff.
 
22
 
 
23
-module(ex_button).
 
24
 
 
25
-include_lib("wx/include/wx.hrl").
 
26
 
 
27
-behavoiur(wx_object).
 
28
-export([start/1, init/1, terminate/2,  code_change/3,
 
29
         handle_info/2, handle_call/3, handle_event/2]).
 
30
 
 
31
-record(state, 
 
32
        {
 
33
          parent,
 
34
          config
 
35
         }).
 
36
 
 
37
start(Config) ->
 
38
    wx_object:start_link(?MODULE, Config, []).
 
39
 
 
40
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
41
init(Config) ->
 
42
        wx:batch(fun() -> do_init(Config) end).
 
43
do_init(Config) ->
 
44
    Parent = proplists:get_value(parent, Config),  
 
45
    Panel = wxScrolledWindow:new(Parent),
 
46
 
 
47
    %% Setup sizers
 
48
    Sz = wxBoxSizer:new(?wxVERTICAL),
 
49
 
 
50
    SzFlags = [{proportion, 0}, {border, 4}, {flag, ?wxALL}],
 
51
    Expand  = [{proportion, 0}, {border, 4}, {flag, ?wxALL bor ?wxEXPAND}],
 
52
 
 
53
    ButtSz = wxStaticBoxSizer:new(?wxHORIZONTAL, Panel, 
 
54
                                  [{label, "wxButton"}]),
 
55
 
 
56
    B10 = wxButton:new(Panel, 10, [{label,"Normal"}]),
 
57
    wxButton:setToolTip(B10, "Normal button with (default) centered label"),
 
58
 
 
59
    B11 = wxToggleButton:new(Panel, 11, "Toggle Button"),
 
60
    wxToggleButton:connect(B11, command_togglebutton_clicked),
 
61
    wxButton:setToolTip(B11, "A toggle button"),
 
62
 
 
63
    B12 = wxButton:new(Panel, 12, [{label,"Default"}]),
 
64
    wxButton:setDefault(B12),
 
65
    wxButton:setToolTip(B12, "Normal button set to be the default button"),
 
66
 
 
67
    B13 = wxButton:new(Panel, 13, [{label,"Disabled"}]),
 
68
    wxButton:disable(B13),
 
69
    wxButton:setToolTip(B13, "Disabled Normal button"),
 
70
    
 
71
    B14 = wxBitmapButton:new(Panel, 14, create_bitmap("A bitmap button")),
 
72
    wxButton:setToolTip(B14, "A Bitmap button"),
 
73
    [wxSizer:add(ButtSz, Button, SzFlags) || Button <- [B10, B11, B12, B13, B14]],
 
74
    
 
75
    %% Alignment and NO_BORDER only works on Win and GTK according to docs.
 
76
    AlignSz = wxStaticBoxSizer:new(?wxHORIZONTAL, Panel, 
 
77
                                   [{label, "Alignment Style"}]),
 
78
 
 
79
    B20 = wxButton:new(Panel, 20, [{label,"Left Aligned"}, {size, {100, -1}}, 
 
80
                                 {style,?wxBU_LEFT}]),
 
81
    wxButton:setToolTip(B20, "Normal button with left aligned label"),
 
82
    
 
83
    B21 = wxButton:new(Panel, 21, [{label,"Top Aligned"},  {size, {-1, 50}},
 
84
                                 {style,?wxBU_TOP}]),
 
85
    wxButton:setToolTip(B21, "Normal button with top aligned label"),
 
86
 
 
87
    B22 = wxButton:new(Panel, 22, [{label,"Lower Right Aligned"},  {size, {150, 50}},
 
88
                                 {style,?wxBU_BOTTOM bor ?wxBU_RIGHT}]),
 
89
    wxButton:setToolTip(B22, "Normal button with top right aligned label"),
 
90
    [wxSizer:add(AlignSz, Button, SzFlags) || Button <- [B20,B21,B22]],
 
91
 
 
92
    %% Other types
 
93
    OtherSz = wxStaticBoxSizer:new(?wxHORIZONTAL, Panel, 
 
94
                                   [{label, "Other Styles"}]),
 
95
 
 
96
    B30 = wxButton:new(Panel, 30, [{label,"Flat Style"}, {style, ?wxNO_BORDER}]),
 
97
    wxButton:setToolTip(B30, "Flat style button, on some OS'es"),
 
98
    
 
99
    B31 = wxButton:new(Panel, 31, [{label,"Exact Fit"}, {style, ?wxBU_EXACTFIT}]),
 
100
    wxButton:setToolTip(B31, "Minimal Size button"),
 
101
 
 
102
    [wxSizer:add(OtherSz, Button, SzFlags) || Button <- [B30,B31]],
 
103
 
 
104
    %% Stock Buttons
 
105
    StockTopSz = wxStaticBoxSizer:new(?wxHORIZONTAL, Panel, 
 
106
                                      [{label, "Stock Buttons"}]),
 
107
 
 
108
    StockButts = [wxButton:new(Panel, Id) || Id <- stock_buttons()],        
 
109
    StockSz = wxGridSizer:new(0,5,3,3),
 
110
    [wxSizer:add(StockSz, Butt, SzFlags) || Butt <- StockButts],
 
111
    wxSizer:add(StockTopSz, StockSz, SzFlags),
 
112
    
 
113
    %% Add to Main sizer
 
114
    [wxSizer:add(Sz, Button, Flag) || 
 
115
        {Button, Flag} <- [{ButtSz,SzFlags},{AlignSz,Expand},
 
116
                           {OtherSz,Expand}, {StockTopSz, Expand}]],
 
117
    
 
118
    wxWindow:connect(Panel, command_button_clicked),
 
119
    wxWindow:setSizer(Panel, Sz),
 
120
    wxSizer:layout(Sz),
 
121
    wxScrolledWindow:setScrollRate(Panel, 5, 5),
 
122
    {Panel, #state{parent=Panel, config=Config}}.
 
123
 
 
124
stock_buttons() ->
 
125
    [?wxID_ABOUT,
 
126
     ?wxID_ADD,
 
127
     ?wxID_APPLY,
 
128
     ?wxID_BOLD,
 
129
     ?wxID_CANCEL,
 
130
     ?wxID_CLEAR,
 
131
     ?wxID_CLOSE,
 
132
     ?wxID_COPY,
 
133
     ?wxID_CUT,
 
134
     ?wxID_DELETE,
 
135
     ?wxID_EDIT,
 
136
     ?wxID_FIND,
 
137
     ?wxID_FILE,
 
138
     ?wxID_REPLACE,
 
139
     ?wxID_BACKWARD,
 
140
     ?wxID_DOWN,
 
141
     ?wxID_FORWARD,
 
142
     ?wxID_UP,
 
143
     ?wxID_HELP,
 
144
     ?wxID_HOME,
 
145
     ?wxID_INDENT,
 
146
     ?wxID_INDEX,
 
147
     ?wxID_ITALIC,
 
148
     ?wxID_JUSTIFY_CENTER,
 
149
     ?wxID_JUSTIFY_FILL,
 
150
     ?wxID_JUSTIFY_LEFT,
 
151
     ?wxID_JUSTIFY_RIGHT,
 
152
     ?wxID_NEW,
 
153
     ?wxID_NO,
 
154
     ?wxID_OK,
 
155
     ?wxID_OPEN,
 
156
     ?wxID_PASTE,
 
157
     ?wxID_PREFERENCES,
 
158
     ?wxID_PRINT,
 
159
     ?wxID_PREVIEW,
 
160
     ?wxID_PROPERTIES,
 
161
     ?wxID_EXIT,
 
162
     ?wxID_REDO,
 
163
     ?wxID_REFRESH,
 
164
     ?wxID_REMOVE,
 
165
     ?wxID_REVERT_TO_SAVED,
 
166
     ?wxID_SAVE,
 
167
     ?wxID_SAVEAS,
 
168
     ?wxID_SELECTALL,
 
169
     ?wxID_STOP,
 
170
     ?wxID_UNDELETE,
 
171
     ?wxID_UNDERLINE,
 
172
     ?wxID_UNDO,
 
173
     ?wxID_UNINDENT,
 
174
     ?wxID_YES,
 
175
     ?wxID_ZOOM_100,
 
176
     ?wxID_ZOOM_FIT,
 
177
     ?wxID_ZOOM_IN,
 
178
     ?wxID_ZOOM_OUT].
 
179
 
 
180
 
 
181
%%%%%%%%%%%%
 
182
%% Async Events are handled in handle_event as in handle_info
 
183
handle_event(#wx{id=Id, event=#wxCommand{type=command_button_clicked}}, 
 
184
             State = #state{parent=Parent}) ->
 
185
    B0 = wxWindow:findWindowById(Id, [{parent, Parent}]),
 
186
    Butt = wx:typeCast(B0, wxButton),
 
187
    Label = wxButton:getLabel(Butt),
 
188
    demo:format(State#state.config,"Button: \'~ts\' clicked~n",[Label]),
 
189
    {noreply,State};
 
190
 
 
191
handle_event(#wx{event=#wxCommand{type=command_togglebutton_clicked}}, 
 
192
             State = #state{}) ->
 
193
    demo:format(State#state.config,"Button: You toggled the 'Toggle button' ~n",[]),
 
194
    {noreply,State};
 
195
 
 
196
handle_event(Ev = #wx{}, State = #state{}) ->
 
197
    demo:format(State#state.config,"Got Event ~p~n",[Ev]),
 
198
    {noreply,State}.
 
199
 
 
200
%% Callbacks handled as normal gen_server callbacks
 
201
handle_info(Msg, State) ->
 
202
    demo:format(State#state.config, "Got Info ~p~n",[Msg]),
 
203
    {noreply,State}.
 
204
 
 
205
handle_call(Msg, _From, State) ->
 
206
    demo:format(State#state.config,"Got Call ~p~n",[Msg]),
 
207
    {reply,ok,State}.
 
208
 
 
209
code_change(_, _, State) ->
 
210
    {stop, ignore, State}.
 
211
 
 
212
terminate(_Reason, _State) ->
 
213
    ok.
 
214
 
 
215
%%%%%  a copy from wxwidgets samples.
 
216
create_bitmap(Label) ->
 
217
    Bmp = wxBitmap:new(140, 30),
 
218
    DC = wxMemoryDC:new(),
 
219
    wxMemoryDC:selectObject(DC,  Bmp),
 
220
    wxDC:setBackground(DC, ?wxWHITE_BRUSH),
 
221
    wxDC:clear(DC),
 
222
    wxDC:setTextForeground(DC, ?wxBLUE),
 
223
    wxDC:drawLabel(DC, Label, {5,5,130,20}, [{alignment, ?wxALIGN_CENTER}]),
 
224
    wxMemoryDC:destroy(DC),
 
225
    Bmp.
 
226
 
 
227