~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/wx/examples/demo/ex_canvas_paint.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_paint).
 
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
          pen,
 
38
          brush,
 
39
          old_pos,
 
40
          bitmap
 
41
        }).
 
42
 
 
43
start(Config) ->
 
44
    wx_object:start_link(?MODULE, Config, []).
 
45
 
 
46
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
47
init(Config) ->
 
48
    wx:batch(fun() -> do_init(Config) end).
 
49
 
 
50
do_init(Config) ->
 
51
    Parent = proplists:get_value(parent, Config),  
 
52
    Panel = wxPanel:new(Parent, []),
 
53
    
 
54
    %% Setup sizers
 
55
    MainSizer = wxBoxSizer:new(?wxVERTICAL),
 
56
    Sizer = wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
57
                                 [{label, "wxDC"}]),
 
58
    Canvas = wxPanel:new(Panel, [{style, ?wxFULL_REPAINT_ON_RESIZE}]),
 
59
    wxPanel:setToolTip(Panel,
 
60
                       "Left-click and hold to draw something - release to stop drawing.\n"
 
61
                       "Middle-click to fill with pink\n"
 
62
                       "Middle-dclick to fill with white.\n"
 
63
                       "Right-click to clear."),
 
64
 
 
65
    Brush = wxBrush:new(?wxWHITE),
 
66
    Pen = wxPen:new(?wxBLACK, [{width, 2}]),
 
67
 
 
68
    %% Add to sizers
 
69
    wxSizer:add(Sizer, Canvas, [{flag, ?wxEXPAND},
 
70
                                {proportion, 1}]),
 
71
 
 
72
    wxSizer:add(MainSizer, Sizer, [{flag, ?wxEXPAND},
 
73
                                   {proportion, 1}]),
 
74
    {W,H} = wxPanel:getSize(Canvas),
 
75
    Bitmap = wxBitmap:new(W,H),
 
76
    
 
77
    wxPanel:connect(Canvas, paint, [callback]),
 
78
    wxPanel:connect(Canvas, size),
 
79
    wxPanel:connect(Canvas, left_down),
 
80
    wxPanel:connect(Canvas, left_dclick),
 
81
    wxPanel:connect(Canvas, left_up),
 
82
    wxPanel:connect(Canvas, right_down),
 
83
    wxPanel:connect(Canvas, middle_down),
 
84
    wxPanel:connect(Canvas, middle_dclick),
 
85
    wxPanel:setSizer(Panel, MainSizer),
 
86
    wxSizer:layout(MainSizer),
 
87
    {Panel, #state{parent=Panel, config=Config,
 
88
                   canvas = Canvas, pen = Pen,
 
89
                   brush = Brush, bitmap = Bitmap}}.
 
90
 
 
91
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
92
%% Callbacks handled as normal gen_server callbacks
 
93
handle_info(Msg, State) ->
 
94
    demo:format(State#state.config, "Got Info ~p\n", [Msg]),
 
95
    {noreply, State}.
 
96
 
 
97
handle_call(Msg, _From, State) ->
 
98
    demo:format(State#state.config, "Got Call ~p\n", [Msg]),
 
99
    {reply,{error, nyi}, State}.
 
100
 
 
101
%% Sync event from callback events, paint event must be handled in callbacks
 
102
%% otherwise nothing will be drawn on windows.
 
103
handle_sync_event(#wx{event = #wxPaint{}}, _wxObj, #state{canvas=Canvas, bitmap=Bitmap}) ->
 
104
    DC = wxPaintDC:new(Canvas),
 
105
    redraw(DC, Bitmap),
 
106
    wxPaintDC:destroy(DC),
 
107
    ok.
 
108
 
 
109
%% Async Events are handled in handle_event as in handle_info
 
110
%% Draw a line
 
111
handle_event(#wx{event = #wxMouse{type = motion, x = X, y = Y}},
 
112
             State = #state{canvas = Canvas, pen = Pen, brush = Brush}) ->
 
113
    Fun =
 
114
        fun(DC) -> wxDC:setPen(DC, Pen),
 
115
                   wxBrush:setColour(Brush, ?wxBLACK),
 
116
                   wxDC:setBrush(DC, Brush),
 
117
                   wxDC:drawLine(DC, {X,Y}, State#state.old_pos)
 
118
        end,
 
119
    draw(Canvas,State#state.bitmap, Fun),
 
120
    {noreply, State#state{old_pos = {X,Y}}};
 
121
handle_event(#wx{event = #wxSize{size = {W,H}}}, State = #state{bitmap=Prev}) ->
 
122
    wxBitmap:destroy(Prev),
 
123
    Bitmap = wxBitmap:new(W,H),
 
124
    draw(State#state.canvas, Bitmap, fun(DC) -> wxDC:clear(DC) end),
 
125
    {noreply, State#state{bitmap=Bitmap}};
 
126
handle_event(#wx{event = #wxMouse{type = left_dclick,x = X,y = Y}}, State = #state{}) ->
 
127
    wxPanel:connect(State#state.canvas, motion),
 
128
    {noreply, State#state{old_pos = {X,Y}}};
 
129
handle_event(#wx{event = #wxMouse{type = left_down,x = X,y = Y}}, State = #state{}) ->
 
130
    wxPanel:connect(State#state.canvas, motion),
 
131
    {noreply, State#state{old_pos = {X,Y}}};
 
132
 
 
133
%% Fill with pink color
 
134
handle_event(#wx{event = #wxMouse{type = middle_down,x = X, y =Y}}, State = #state{}) ->
 
135
    Fun =
 
136
        fun(DC) -> wxBrush:setColour(State#state.brush, {255,125,255,255}),
 
137
                   wxDC:setBrush(DC, State#state.brush),
 
138
                   wxDC:floodFill(DC, {X,Y}, ?wxBLACK, [{style, ?wxFLOOD_BORDER}])
 
139
        end,
 
140
    
 
141
    draw(State#state.canvas, State#state.bitmap, Fun),
 
142
    {noreply, State};
 
143
 
 
144
%% Fill with white color
 
145
handle_event(#wx{event = #wxMouse{type = middle_dclick,x = X, y =Y}}, State = #state{}) ->
 
146
    Fun =
 
147
        fun(DC) -> wxBrush:setColour(State#state.brush, ?wxWHITE),
 
148
                   wxDC:setBrush(DC, State#state.brush),
 
149
                   wxDC:floodFill(DC, {X,Y}, ?wxBLACK, [{style, ?wxFLOOD_BORDER}])
 
150
        end,
 
151
    
 
152
    draw(State#state.canvas,  State#state.bitmap,Fun),
 
153
    {noreply, State};
 
154
handle_event(#wx{event = #wxMouse{type = left_up}}, State = #state{}) ->
 
155
    wxPanel:disconnect(State#state.canvas, motion),
 
156
    {noreply, State};
 
157
handle_event(#wx{event = #wxMouse{type = right_down}}, State = #state{}) ->
 
158
    draw(State#state.canvas, State#state.bitmap, fun(DC) -> wxDC:clear(DC) end),
 
159
    {noreply, State};
 
160
handle_event(Ev = #wx{}, State = #state{}) ->
 
161
    demo:format(State#state.config, "Got Event ~p\n", [Ev]),
 
162
    {noreply, State}.
 
163
 
 
164
code_change(_, _, State) ->
 
165
    {stop, ignore, State}.
 
166
 
 
167
terminate(_Reason, _State) ->
 
168
    ok.
 
169
 
 
170
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
171
%% Local functions
 
172
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
173
 
 
174
draw(Canvas, Bitmap, Fun) ->
 
175
    MemoryDC = wxMemoryDC:new(Bitmap),
 
176
    CDC = wxClientDC:new(Canvas),
 
177
 
 
178
    Fun(MemoryDC),
 
179
    
 
180
    wxDC:blit(CDC, {0,0},
 
181
              {wxBitmap:getWidth(Bitmap), wxBitmap:getHeight(Bitmap)},
 
182
              MemoryDC, {0,0}),
 
183
    
 
184
    wxClientDC:destroy(CDC),
 
185
    wxMemoryDC:destroy(MemoryDC).
 
186
 
 
187
 
 
188
redraw(DC, Bitmap) ->
 
189
    MemoryDC = wxMemoryDC:new(Bitmap),
 
190
 
 
191
    wxDC:blit(DC, {0,0},
 
192
              {wxBitmap:getWidth(Bitmap), wxBitmap:getHeight(Bitmap)},
 
193
              MemoryDC, {0,0}),
 
194
 
 
195
    wxMemoryDC:destroy(MemoryDC).
 
196
 
 
197