~ubuntu-branches/ubuntu/lucid/erlang/lucid-proposed

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

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_popupMenu).
 
20
 
 
21
-behavoiur(wx_object).
 
22
 
 
23
%% Client API
 
24
-export([start/1]).
 
25
 
 
26
%% wx_object callbacks
 
27
-export([init/1, terminate/2,  code_change/3,
 
28
         handle_info/2, handle_call/3, handle_event/2]).
 
29
 
 
30
-include_lib("wx/include/wx.hrl").
 
31
 
 
32
-record(state, 
 
33
        {
 
34
          parent,
 
35
          config,
 
36
          menu
 
37
        }).
 
38
 
 
39
start(Config) ->
 
40
    wx_object:start_link(?MODULE, Config, []).
 
41
 
 
42
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
43
init(Config) ->
 
44
    wx:batch(fun() -> do_init(Config) end).
 
45
 
 
46
do_init(Config) ->
 
47
    Parent = proplists:get_value(parent, Config),  
 
48
    Panel = wxPanel:new(Parent, []),
 
49
 
 
50
    %% Setup sizers
 
51
    MainSizer = wxBoxSizer:new(?wxVERTICAL),
 
52
    Sizer = wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
53
                                 [{label, "Popup Menu"}]),
 
54
 
 
55
    Text = wxStaticText:new(Panel, ?wxID_ANY, "Right click to open popup menu", []),
 
56
 
 
57
 
 
58
    %% Add to sizers
 
59
    wxSizer:add(Sizer, Text, [{border, 20},
 
60
                              {flag, ?wxALL}]),
 
61
 
 
62
    wxSizer:add(MainSizer, Sizer, [{flag, ?wxEXPAND},
 
63
                                   {proportion, 1}]),
 
64
 
 
65
    wxPanel:connect(Panel, right_up),
 
66
    wxPanel:setSizer(Panel, MainSizer),
 
67
    {Panel, #state{parent=Panel, config=Config,
 
68
                   menu = create_menu()}}.
 
69
 
 
70
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
71
%% Callbacks handled as normal gen_server callbacks
 
72
handle_info(Msg, State) ->
 
73
    demo:format(State#state.config, "Got Info ~p\n", [Msg]),
 
74
    {noreply, State}.
 
75
 
 
76
handle_call(Msg, _From, State) ->
 
77
    demo:format(State#state.config, "Got Call ~p\n", [Msg]),
 
78
    {reply,{error, nyi}, State}.
 
79
 
 
80
%% Async Events are handled in handle_event as in handle_info
 
81
handle_event(#wx{obj = Panel,
 
82
                 event = #wxMouse{type = right_up}},
 
83
             State = #state{menu = Menu}) ->
 
84
    wxWindow:popupMenu(Panel, Menu),
 
85
    {noreply, State};
 
86
handle_event(#wx{obj = Menu,
 
87
                 id = Id,
 
88
                 event = #wxCommand{type = command_menu_selected}},
 
89
             State = #state{}) ->
 
90
    Label = wxMenu:getLabel(Menu, Id),
 
91
    demo:format(State#state.config, "wxMenu clicked ~p\n", [Label]),
 
92
    {noreply, State};
 
93
handle_event(Ev = #wx{}, State = #state{}) ->
 
94
    demo:format(State#state.config, "Got Event ~p\n", [Ev]),
 
95
    {noreply, State}.
 
96
 
 
97
code_change(_, _, State) ->
 
98
    {stop, ignore, State}.
 
99
 
 
100
terminate(_Reason, _State) ->
 
101
    ok.
 
102
 
 
103
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
104
%% Local functions
 
105
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
106
 
 
107
create_menu() ->
 
108
    Menu = wxMenu:new([]),
 
109
    SubMenu  = wxMenu:new([]),
 
110
    SubMenu2 = wxMenu:new([]),
 
111
 
 
112
    wxMenu:append(Menu, ?wxID_UNDO, "Undo", []),
 
113
    wxMenu:append(Menu, ?wxID_REDO, "Redo", []),
 
114
    wxMenu:append(Menu, ?wxID_HELP, "Help", []),
 
115
    wxMenu:appendSeparator(Menu),
 
116
    wxMenu:appendCheckItem(Menu, ?wxID_ANY, "Check item", []),
 
117
    wxMenu:appendSeparator(Menu),
 
118
    wxMenu:appendRadioItem(Menu, ?wxID_ANY, "Radio item 1", []),
 
119
    wxMenu:appendRadioItem(Menu, ?wxID_ANY, "Radio item 2", []),
 
120
    wxMenu:appendRadioItem(Menu, ?wxID_ANY, "Radio item 3", []),
 
121
    wxMenu:appendRadioItem(Menu, ?wxID_ANY, "Radio item 4", []),
 
122
 
 
123
    wxMenu:appendSeparator(Menu),
 
124
    wxMenuItem:enable(wxMenu:append(Menu, ?wxID_ANY, "Disabled", []), [{enable,false}]),
 
125
    wxMenu:appendSeparator(Menu),
 
126
 
 
127
    wxMenu:append(SubMenu, ?wxID_ABOUT, "About", []),
 
128
    wxMenu:append(SubMenu, ?wxID_ANY, "Sub Item2", []),
 
129
    wxMenu:append(SubMenu, ?wxID_SAVE, "Save", []),
 
130
    wxMenu:break(SubMenu),
 
131
    wxMenu:append(SubMenu, ?wxID_EXIT, "Exit", []),
 
132
    wxMenu:append(SubMenu, ?wxID_OPEN, "Open", []),
 
133
    wxMenu:append(SubMenu, ?wxID_NEW, "New", []),
 
134
    wxMenu:append(Menu, ?wxID_ANY, "Sub menu", SubMenu, []),
 
135
 
 
136
    wxMenu:appendCheckItem(SubMenu2, ?wxID_ANY, "Check Item", []),
 
137
    wxMenu:appendSeparator(SubMenu2),
 
138
    wxMenu:append(SubMenu2, ?wxID_CLEAR, "Clear", []),
 
139
    wxMenu:append(SubMenu2, ?wxID_ANY, "Sub Item", []),
 
140
 
 
141
    Bitmap = wxArtProvider:getBitmap("wxART_NEW"),
 
142
    AnotherSubMenu = wxMenuItem:new([{parentMenu, Menu},
 
143
                                     {id, ?wxID_ANY},
 
144
                                     {text, "Another sub menu"},
 
145
                                     {subMenu, SubMenu2},
 
146
                                     {kind, ?wxITEM_NORMAL}]),
 
147
    wxMenuItem:setBitmap(AnotherSubMenu, Bitmap),
 
148
    wxMenu:append(Menu, AnotherSubMenu),
 
149
 
 
150
    wxMenu:connect(Menu, command_menu_selected),
 
151
    wxMenu:connect(SubMenu, command_menu_selected),
 
152
    wxMenu:connect(SubMenu2, command_menu_selected),
 
153
    Menu.