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

« back to all changes in this revision

Viewing changes to lib/wx/examples/demo/ex_canvas.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_canvas).
 
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, handle_sync_event/3]).
 
29
 
 
30
-include_lib("wx/include/wx.hrl").
 
31
 
 
32
-record(state, 
 
33
        {
 
34
          parent,
 
35
          config,
 
36
          canvas,
 
37
          bitmap
 
38
        }).
 
39
 
 
40
start(Config) ->
 
41
    wx_object:start_link(?MODULE, Config, []).
 
42
 
 
43
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
44
init(Config) ->
 
45
    wx:batch(fun() -> do_init(Config) end).
 
46
 
 
47
do_init(Config) ->
 
48
    Parent = proplists:get_value(parent, Config),  
 
49
    Panel = wxPanel:new(Parent, []),
 
50
 
 
51
    %% Setup sizers
 
52
    MainSizer = wxBoxSizer:new(?wxVERTICAL),
 
53
    Sizer = wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
54
                                 [{label, "Various shapes"}]),
 
55
    Button = wxButton:new(Panel, ?wxID_ANY, [{label, "Redraw"}]),
 
56
 
 
57
    Canvas = wxPanel:new(Panel, []),
 
58
 
 
59
    %% Add to sizers
 
60
    wxSizer:add(Sizer, Button),
 
61
    wxSizer:add(Sizer, Canvas, [{flag, ?wxEXPAND},
 
62
                                {proportion, 1}]),
 
63
 
 
64
    wxSizer:add(MainSizer, Sizer, [{flag, ?wxEXPAND},
 
65
                                   {proportion, 1}]),
 
66
 
 
67
    {W,H} = wxPanel:getSize(Canvas),
 
68
    Bitmap = wxBitmap:new(W,H),
 
69
 
 
70
    wxPanel:connect(Canvas, paint, [callback]),
 
71
    wxPanel:connect(Canvas, size),
 
72
    wxPanel:connect(Button, command_button_clicked),
 
73
    wxPanel:setSizer(Panel, MainSizer),
 
74
    {Panel, #state{parent=Panel, config=Config,
 
75
                   canvas = Canvas, bitmap = Bitmap}}.
 
76
 
 
77
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
78
%% Callbacks handled as normal gen_server callbacks
 
79
handle_info(Msg, State) ->
 
80
    demo:format(State#state.config, "Got Info ~p\n", [Msg]),
 
81
    {noreply, State}.
 
82
 
 
83
handle_call(Msg, _From, State) ->
 
84
    demo:format(State#state.config, "Got Call ~p\n", [Msg]),
 
85
    {reply,{error, nyi}, State}.
 
86
 
 
87
%% Sync event from callback events, paint event must be handled in callbacks
 
88
%% otherwise nothing will be drawn on windows.
 
89
handle_sync_event(#wx{event = #wxPaint{}}, _wxObj,
 
90
                  #state{canvas=Canvas, bitmap=Bitmap}) ->
 
91
    DC = wxPaintDC:new(Canvas),
 
92
    redraw(DC, Bitmap),
 
93
    wxPaintDC:destroy(DC),
 
94
    ok.
 
95
 
 
96
%% Async Events are handled in handle_event as in handle_info
 
97
handle_event(#wx{event = #wxCommand{type = command_button_clicked}},
 
98
             State = #state{}) ->
 
99
    Image = wxImage:new("image.jpg"),
 
100
    Image2 = wxImage:scale(Image, wxImage:getWidth(Image) div 3,
 
101
                           wxImage:getHeight(Image) div 3),
 
102
    Bmp = wxBitmap:new(Image2),
 
103
    wxImage:destroy(Image),
 
104
    wxImage:destroy(Image2),
 
105
    {W,H} = wxPanel:getSize(State#state.canvas),
 
106
    Positions = lists:map(fun(_) ->
 
107
                                  get_pos(W,H)
 
108
                          end, lists:seq(1,(W+H) div 20)),
 
109
    draw(State#state.canvas, State#state.bitmap, fun(DC) -> wxDC:clear(DC) end),
 
110
    Fun = fun(DC) ->
 
111
                  lists:foreach(fun({X,Y}=Pos) ->
 
112
                                        wxDC:setBrush(DC, ?wxTRANSPARENT_BRUSH),
 
113
                                        wxDC:setPen(DC, wxPen:new(?wxBLACK, [{width, 2}])),
 
114
                                        case X rem 6 of
 
115
                                            0 -> wxDC:drawBitmap(DC, Bmp, Pos);
 
116
                                            1 -> wxDC:setBrush(DC, ?wxRED_BRUSH),
 
117
                                                 wxDC:drawRectangle(DC, Pos, {20,20});
 
118
                                            2 -> wxDC:setBrush(DC, ?wxBLUE_BRUSH),
 
119
                                                 wxDC:drawCircle(DC, {X+10, Y+10}, 15);
 
120
                                            3 -> wxDC:setPen(DC, wxPen:new({200,200,0,255}, [{width, 4}])),
 
121
                                                 wxDC:drawLine(DC, Pos, get_pos(W,H));
 
122
                                            4 -> wxDC:setBrush(DC, ?wxGREEN_BRUSH),
 
123
                                                 wxDC:drawEllipse(DC, Pos, {60,20});
 
124
                                            _ -> wxDC:drawLabel(DC, "Erlang /", {X,Y,60,20}),
 
125
                                                 wxDC:drawRotatedText(DC, "OTP", {X+60,Y}, 340.0)
 
126
                                        end
 
127
                                end, Positions)
 
128
          end,
 
129
    draw(State#state.canvas, State#state.bitmap, Fun),
 
130
    wxBitmap:destroy(Bmp),
 
131
    {noreply, State};
 
132
handle_event(#wx{event = #wxSize{size = {W,H}}},
 
133
             State = #state{bitmap = Prev}) ->
 
134
    Bitmap = wxBitmap:new(W,H),
 
135
    draw(State#state.canvas, Bitmap, fun(DC) -> wxDC:clear(DC) end),
 
136
    wxBitmap:destroy(Prev),
 
137
    {noreply, State#state{bitmap = Bitmap}};
 
138
handle_event(Ev = #wx{}, State = #state{}) ->
 
139
    demo:format(State#state.config, "Got Event ~p\n", [Ev]),
 
140
    {noreply, State}.
 
141
 
 
142
code_change(_, _, State) ->
 
143
    {stop, ignore, State}.
 
144
 
 
145
terminate(_Reason, _State) ->
 
146
    ok.
 
147
 
 
148
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
149
%% Local functions
 
150
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
151
 
 
152
%% Buffered makes it all appear on the screen at the same time
 
153
draw(Canvas, Bitmap, Fun) ->
 
154
    MemoryDC = wxMemoryDC:new(Bitmap),
 
155
    CDC = wxClientDC:new(Canvas),
 
156
 
 
157
    Fun(MemoryDC),
 
158
    
 
159
    wxDC:blit(CDC, {0,0},
 
160
              {wxBitmap:getWidth(Bitmap), wxBitmap:getHeight(Bitmap)},
 
161
              MemoryDC, {0,0}),
 
162
    
 
163
    wxClientDC:destroy(CDC),
 
164
    wxMemoryDC:destroy(MemoryDC).
 
165
 
 
166
 
 
167
redraw(DC, Bitmap) ->
 
168
    MemoryDC = wxMemoryDC:new(Bitmap),
 
169
 
 
170
    wxDC:blit(DC, {0,0},
 
171
              {wxBitmap:getWidth(Bitmap), wxBitmap:getHeight(Bitmap)},
 
172
              MemoryDC, {0,0}),
 
173
 
 
174
    wxMemoryDC:destroy(MemoryDC).
 
175
 
 
176
 
 
177
get_pos(W,H) ->
 
178
    {random:uniform(W), random:uniform(H)}.