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

« back to all changes in this revision

Viewing changes to lib/wx/examples/demo/ex_choices.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
-module(ex_choices).
 
20
 
 
21
-behavoiur(wx_object).
 
22
 
 
23
-export([start/1, init/1, terminate/2,  code_change/3,
 
24
         handle_info/2, handle_call/3, handle_event/2]).
 
25
 
 
26
-include_lib("wx/include/wx.hrl").
 
27
 
 
28
-record(state, 
 
29
        {
 
30
          parent,
 
31
          config,
 
32
          list_box
 
33
         }).
 
34
 
 
35
 
 
36
start(Config) ->
 
37
    wx_object:start_link(?MODULE, Config, []).
 
38
 
 
39
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
40
init(Config) ->
 
41
        wx:batch(fun() -> do_init(Config) end).
 
42
do_init(Config) ->
 
43
    Parent = proplists:get_value(parent, Config),  
 
44
    Panel = wxScrolledWindow:new(Parent, []),
 
45
 
 
46
    %% Setup sizers
 
47
    MainSizer = wxBoxSizer:new(?wxVERTICAL),
 
48
    ListBoxSizer = wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
49
                                 [{label, "wxListBox"}]),
 
50
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
 
51
    Sizer2 = wxBoxSizer:new(?wxHORIZONTAL),
 
52
 
 
53
    Choices = ["one","two","three",
 
54
               "four","five","six",
 
55
               "seven","eight","nine",
 
56
               "ten", "eleven", "twelve"],
 
57
 
 
58
    %%================%%
 
59
    %%     ListBox    %%
 
60
    %%================%%
 
61
    ListBox = wxListBox:new(Panel, 1, [{size, {-1,100}},
 
62
                                       {choices, ["Multiple selection"|Choices]},
 
63
                                       {style, ?wxLB_MULTIPLE}]),
 
64
    ListBox2 = wxListBox:new(Panel, 2, [{size, {-1,100}},
 
65
                                        {choices, ["Single selection"|Choices]},
 
66
                                        {style, ?wxLB_SINGLE}]),
 
67
 
 
68
    %%================%%
 
69
    %%     Choice     %%
 
70
    %%================%%
 
71
    Sizer3  = wxBoxSizer:new(?wxHORIZONTAL),
 
72
    ChoiceSizer = wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
73
                                 [{label, "wxChoice"}]),
 
74
    Choice = wxChoice:new(Panel, 4, [{choices, Choices}]),
 
75
    wxChoice:connect(Choice,command_choice_selected),
 
76
    %%================%%
 
77
    %%    SpinCtrl    %%
 
78
    %%================%%
 
79
    SpinSizer = wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
80
                                     [{label, "wxSpinCtrl"}]),
 
81
    SpinCtrl = wxSpinCtrl:new(Panel, []),
 
82
    wxSpinCtrl:setRange(SpinCtrl, 0, 100),
 
83
    wxChoice:connect(SpinCtrl,command_spinctrl_updated),
 
84
    %%================%%
 
85
    %%    ComboBox    %%
 
86
    %%================%%
 
87
    ComboSizer = wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
88
                                     [{label, "wxComboBox"}]),
 
89
    ComboBox = wxComboBox:new(Panel, 5, [{choices, Choices}]),
 
90
    wxComboBox:setValue(ComboBox, "Default value"),
 
91
    wxComboBox:connect(ComboBox, command_combobox_selected),
 
92
 
 
93
    %%================%%
 
94
    %%  Add to sizers %%
 
95
    %%================%%
 
96
    Options = [{border,4}, {flag, ?wxALL}],
 
97
    wxSizer:add(Sizer, ListBox, Options),
 
98
    wxSizer:add(Sizer, ListBox2, Options),
 
99
 
 
100
    wxSizer:add(ChoiceSizer, Choice, Options),
 
101
    wxSizer:add(SpinSizer, SpinCtrl, Options),
 
102
    wxSizer:add(Sizer3, ChoiceSizer, []),
 
103
    wxSizer:add(Sizer3, SpinSizer, [{border, 4}, {flag, ?wxLEFT}]),
 
104
 
 
105
    wxSizer:add(ComboSizer, ComboBox, Options),
 
106
 
 
107
    wxSizer:add(ListBoxSizer, Sizer, Options),
 
108
    wxSizer:add(ListBoxSizer, Sizer2, Options),
 
109
    wxSizer:add(MainSizer, ListBoxSizer, Options),
 
110
    wxSizer:add(MainSizer, Sizer3, Options),
 
111
    wxSizer:add(MainSizer, ComboSizer, Options),
 
112
 
 
113
    wxScrolledWindow:setScrollRate(Panel, 5, 5),
 
114
    wxPanel:setSizer(Panel, MainSizer),
 
115
    {Panel, #state{parent=Panel, config=Config,
 
116
                   list_box = ListBox}}.
 
117
 
 
118
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
119
%% Callbacks handled as normal gen_server callbacks
 
120
handle_info(Msg, State) ->
 
121
    demo:format(State#state.config, "Got Info ~p\n",[Msg]),
 
122
    {noreply, State}.
 
123
 
 
124
handle_call(Msg, _From, State) ->
 
125
    demo:format(State#state.config,"Got Call ~p\n",[Msg]),
 
126
    {reply, {error,nyi}, State}.
 
127
 
 
128
%% Async Events are handled in handle_event as in handle_info
 
129
handle_event(#wx{obj = ComboBox,
 
130
                 event = #wxCommand{type = command_combobox_selected}},
 
131
             State = #state{}) ->
 
132
    Value = wxComboBox:getValue(ComboBox),
 
133
    demo:format(State#state.config,"Selected wxComboBox ~p\n",[Value]),
 
134
    {noreply, State};
 
135
handle_event(#wx{event = #wxCommand{type = command_choice_selected,
 
136
                                        cmdString = Value}},
 
137
             State = #state{}) ->
 
138
    demo:format(State#state.config,"Selected wxChoice ~p\n",[Value]),
 
139
    {noreply, State};
 
140
handle_event(#wx{event = #wxSpin{type = command_spinctrl_updated,
 
141
                                 commandInt = Int}},
 
142
             State = #state{}) ->
 
143
    demo:format(State#state.config,"wxSpinCtrl changed to ~p\n",[Int]),
 
144
    {noreply, State};
 
145
handle_event(Ev = #wx{}, State = #state{}) ->
 
146
    demo:format(State#state.config,"Got Event ~p\n",[Ev]),
 
147
    {noreply, State}.
 
148
 
 
149
code_change(_, _, State) ->
 
150
    {stop, ignore, State}.
 
151
 
 
152
terminate(_Reason, _State) ->
 
153
    ok.
 
154
 
 
155
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
156
%% Local functions
 
157
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
158