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

« back to all changes in this revision

Viewing changes to lib/wx/examples/sudoku/sudoku_board.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

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
%%% File    : sud_board.erl
 
20
%%% Author  :  <dgud@erix.ericsson.se>
 
21
%%% Description : Manages the gui board
 
22
%%%
 
23
%%% Created :  9 Jan 2008 by  <dgud@erix.ericsson.se>
 
24
%%%-------------------------------------------------------------------
 
25
-module(sudoku_board).
 
26
 
 
27
-export([new/1, setup_board/2, clear_board/1, left/1,
 
28
         get_board_data/1,set_board_data/2, 
 
29
         set_butt/3, butt_correct/3,
 
30
         draw/3, 
 
31
         %% Callbacks
 
32
         init/1, handle_sync_event/3, 
 
33
         handle_event/2, handle_info/2, handle_call/3, 
 
34
         code_change/3, terminate/2]).
 
35
 
 
36
-include("sudoku.hrl").
 
37
 
 
38
-record(state, {win, parent, board=[], pen, fonts=[]}).
 
39
-record(sq, {key,val,correct=true,given=false}).
 
40
-define(BRD,10).
 
41
-define(ARC_R, 10).
 
42
    
 
43
-behaviour(wx_object).
 
44
 
 
45
%% API 
 
46
new(ParentObj) ->
 
47
    wx_object:start_link(?MODULE, [ParentObj, self()], []).
 
48
 
 
49
setup_board(Board, Init) ->
 
50
    wx_object:call(Board, {setup_board, Init}).
 
51
 
 
52
clear_board(Board) ->
 
53
    wx_object:call(Board, clear_board).
 
54
 
 
55
butt_correct(Board, Key, Correct) ->
 
56
    wx_object:call(Board, {butt_correct, Key, Correct}).
 
57
 
 
58
set_butt(Board, Indx, Val) when is_integer(Indx) ->
 
59
    {R,C,_} = sudoku_game:rcm(Indx),
 
60
    set_butt(Board, {R,C}, Val);
 
61
set_butt(Board, Id, Val) ->
 
62
    wx_object:call(Board, {set_butt, Id, Val}).
 
63
 
 
64
left(Board) ->
 
65
    wx_object:call(Board, left).
 
66
 
 
67
get_board_data(Board) ->
 
68
    wx_object:call(Board, get_board_data).
 
69
set_board_data(Board, List) ->
 
70
    wx_object:call(Board, {set_board_data, List}).
 
71
 
 
72
 
 
73
draw(Board, DC, Size) ->
 
74
    wx_object:call(Board, {draw, DC, Size}).
 
75
 
 
76
 
 
77
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
78
 
 
79
init([ParentObj, ParentPid]) ->
 
80
    Win = wxWindow:new(ParentObj, ?wxID_ANY, [{style, ?wxFULL_REPAINT_ON_RESIZE}]),
 
81
    wxWindow:setFocus(Win), %% Get keyboard focus
 
82
    wxWindow:setSizeHints(Win, {250,250}),
 
83
    wxWindow:connect(Win, paint,  [callback]),
 
84
    wxWindow:connect(Win, size,  []),
 
85
    wxWindow:connect(Win, erase_background, []),
 
86
    wxWindow:connect(Win, key_up, [{skip, true}]),
 
87
    wxWindow:connect(Win, left_down, [{skip, true}]),
 
88
    wxWindow:connect(Win, enter_window, [{skip, true}]), 
 
89
 
 
90
    %% Init pens and fonts
 
91
    Pen = wxPen:new({0,0,0}, [{width, 3}]),
 
92
    Fs0  = [{Sz,wxFont:new(Sz, ?wxSWISS, ?wxNORMAL, ?wxNORMAL,[])} ||
 
93
               Sz <- [8,9,10,11,12,13,14,16,18,20,22,24,26,28,30,34,38,42,44,46]],
 
94
    TestDC  = wxClientDC:new(Win),
 
95
    CW = fun({Sz,Font},Acc) ->
 
96
                 case wxFont:ok(Font) of
 
97
                     true -> 
 
98
                         wxDC:setFont(TestDC, Font),
 
99
                         CH = wxDC:getCharHeight(TestDC), 
 
100
                         [{CH,Sz,Font} | Acc];
 
101
                     false ->
 
102
                         Acc
 
103
                 end
 
104
         end,
 
105
    Fs = lists:foldl(CW, [], Fs0),
 
106
    wxClientDC:destroy(TestDC),    
 
107
    {Win, #state{win=Win, board=[], pen=Pen, fonts=Fs, parent=ParentPid}}.
 
108
 
 
109
handle_sync_event(#wx{event=#wxPaint{}}, _Obj, State = #state{win=Win}) ->
 
110
    %% io:format("EPaint~n",[]),
 
111
    Size = wxWindow:getSize(Win),
 
112
    DC = wxPaintDC:new(Win),
 
113
    wxDC:destroyClippingRegion(DC),
 
114
    redraw(DC,Size,State),
 
115
    wxPaintDC:destroy(DC),
 
116
    %%io:format("...EPaint~n",[]),
 
117
    ok.
 
118
 
 
119
handle_event(#wx{event=#wxMouse{type=enter_window}}, State = #state{win=Win}) ->
 
120
    wxWindow:setFocus(Win), %% Get keyboard focus
 
121
    {noreply,State};
 
122
handle_event(#wx{event=#wxKey{keyCode=KeyC, x=X,y=Y}},
 
123
             S = #state{parent=Pid, win=Win}) ->
 
124
    Val = if KeyC > 47, KeyC < 58 -> KeyC - $0;
 
125
             KeyC > 325, KeyC < 336 -> KeyC - 326; %% NUM LOCK
 
126
             true -> 0
 
127
          end,    
 
128
    case get_butt(X,Y,S) of
 
129
        error ->   %% Mac don't get correct coordinates.
 
130
            Global = wx_misc:getMousePosition(),
 
131
            {CX,CY} = wxWindow:screenToClient(Win, Global),
 
132
            case get_butt(CX,CY,S) of 
 
133
                error -> ignore;
 
134
                Id -> Pid ! {set_val,Id,Val}
 
135
            end;
 
136
        Id -> 
 
137
            Pid ! {set_val,Id,Val} 
 
138
    end,
 
139
    {noreply, S};
 
140
handle_event(#wx{event=#wxMouse{type=left_down,x=X,y=Y}},
 
141
             S = #state{parent=Gui, win=F}) ->
 
142
    Id = get_butt(X,Y,S),
 
143
    case Id of
 
144
        error -> ignore;
 
145
        _ -> create_popup_menu(Gui,Id,X,Y,F)
 
146
    end,
 
147
    {noreply, S};
 
148
handle_event(#wx{event=#wxSize{}}, State) ->
 
149
    redraw(State),          
 
150
    {noreply,State};
 
151
handle_event(_Ev, State) ->
 
152
    {noreply,State}.
 
153
 
 
154
%%%%%%%%%%%%%%%%%%%
 
155
 
 
156
handle_call({set_butt, Key, 0},_From,S0=#state{board=B0}) ->  %% Reset
 
157
    B = lists:keydelete(Key,2,B0),
 
158
    S = S0#state{board=B},
 
159
    redraw(S),
 
160
    {reply, ok, S};
 
161
 
 
162
handle_call({set_butt, Key, Val},_From,S0=#state{board=B0}) ->  
 
163
    case lists:keysearch(Key,2,B0) of
 
164
        {value, _} -> 
 
165
            B = lists:keyreplace(Key, 2, B0, #sq{key=Key,val=Val});
 
166
        false ->
 
167
            B = [#sq{key=Key, val=Val}|B0]
 
168
    end,
 
169
    S = S0#state{board=B},
 
170
    redraw(S),
 
171
    {reply, ok, S};
 
172
 
 
173
handle_call({butt_correct, Key, Correct},_From, S0=#state{board=B0}) ->
 
174
    case lists:keysearch(Key,2,B0) of
 
175
        {value, Butt} -> 
 
176
            B = lists:keyreplace(Key, 2, B0, Butt#sq{key=Key,correct=Correct});
 
177
        false ->
 
178
            B = B0          
 
179
    end,
 
180
    S = S0#state{board=B},
 
181
    redraw(S),
 
182
    {reply, ok, S};
 
183
 
 
184
handle_call({setup_board, Init},_From, State) ->
 
185
    B = [#sq{given=true, correct=true, key=Key, val=Val} || {Key,Val} <- Init],
 
186
    S = State#state{board=B},
 
187
    redraw(S),
 
188
    {reply, ok, S};
 
189
 
 
190
handle_call(clear_board,_From, State = #state{board=B0}) ->    
 
191
    B = [Butt || Butt = #sq{given=true} <- B0],
 
192
    S = State#state{board=B},
 
193
    redraw(S),
 
194
    Given = [{Key, Val} || #sq{key=Key,val=Val,given=true} <- B],
 
195
    {reply, Given, S};
 
196
handle_call(get_board_data,_From, S=#state{board=B0}) ->    
 
197
    {reply, B0, S};
 
198
handle_call({set_board_data, B},_From, S0) ->    
 
199
    S = S0#state{board=B},
 
200
    redraw(S),
 
201
    G1 = [{Key, Val} || #sq{key=Key,val=Val,given=true} <- B],
 
202
    G2 = [{Key, Val} || #sq{key=Key,val=Val,given=false,correct=true} <- B],
 
203
    G3 = [{Key, Val} || #sq{key=Key,val=Val,given=false,correct=false} <- B],
 
204
    {reply, G1 ++ G2 ++ G3, S};
 
205
handle_call(left,_From, S = #state{board=B}) ->
 
206
    Res = 81 - length([ok || #sq{correct=C} <- B, C /= false]),
 
207
    {reply, Res, S};
 
208
handle_call({draw, DC, Size},_From, S) ->    
 
209
    redraw(DC,Size,S),
 
210
    {reply, ok, S}.
 
211
 
 
212
code_change(_, _, State) ->
 
213
    {stop, not_yet_implemented, State}.
 
214
 
 
215
handle_info(Msg, State) ->
 
216
    {stop, {info, Msg}, State}.
 
217
 
 
218
terminate(_Reason, _State) ->
 
219
    normal.
 
220
 
 
221
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
222
 
 
223
 
 
224
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
225
 
 
226
get_butt(X, Y, #state{win=Win}) ->
 
227
    {W0,H0} = wxWindow:getSize(Win),
 
228
    BoxSz = getGeomSz(W0,H0),
 
229
    %%    io:format("~p ~p ~p ~p~n", [{X,Y}, {W0,H0}, BoxSz, calc_pos(X-?BRD,Y-?BRD, BoxSz)]),
 
230
    case calc_pos(X-?BRD,Y-?BRD, BoxSz) of
 
231
        Pos = {R,C} when 0 < R, R < 10, 0 < C, C < 10 -> Pos;
 
232
        _ -> error
 
233
    end.
 
234
 
 
235
calc_pos(X,Y, BoxSz) ->
 
236
    {1+(Y*3 div BoxSz), 1+(X*3 div BoxSz)}.
 
237
 
 
238
redraw(S = #state{win=Win}) ->
 
239
    DC0  = wxClientDC:new(Win),
 
240
    DC   = wxBufferedDC:new(DC0),
 
241
    Size = wxWindow:getSize(Win),
 
242
    redraw(DC, Size, S),
 
243
    wxBufferedDC:destroy(DC),
 
244
    wxClientDC:destroy(DC0),
 
245
    ok.
 
246
 
 
247
redraw(DC, Size, S) ->    
 
248
    wx:batch(fun() -> 
 
249
                     wxDC:setBackground(DC, ?wxWHITE_BRUSH),
 
250
                     wxDC:clear(DC),
 
251
                     BoxSz = draw_board(DC,Size,S),
 
252
                     F = sel_font(BoxSz div 3,S#state.fonts),
 
253
                     [draw_number(DC,F,BoxSz,Sq) || Sq <- S#state.board]
 
254
             end).
 
255
 
 
256
sel_font(_BS,[{_H,_Sz,F}]) ->
 
257
    %%   io:format("Font sz ~p height ~p in BS ~p~n",[_Sz,_H, _BS]),
 
258
    F;
 
259
sel_font(BS,[{H,_Sz,F}|_]) when BS > (H + 6) -> 
 
260
    %%   io:format("Font sz ~p height ~p in BS ~p~n",[_Sz,H, BS]),
 
261
    F;
 
262
sel_font(BS,[_|Fs]) ->
 
263
    sel_font(BS,Fs).
 
264
 
 
265
draw_number(DC,F,Sz,#sq{key={R,C},val=Num,given=Bold,correct=Correct}) ->
 
266
    {X,Y} = get_coords(Sz,R-1,C-1),
 
267
    TBox = Sz div 3,
 
268
    if Bold -> 
 
269
            wxFont:setWeight(F,?wxBOLD),
 
270
            wxDC:setTextForeground(DC,{0,0,0});
 
271
       Correct =:= false ->
 
272
            wxFont:setWeight(F,?wxNORMAL),
 
273
            wxDC:setTextForeground(DC,{255,40,40,255});
 
274
       true ->
 
275
            wxFont:setWeight(F,?wxNORMAL),
 
276
            wxDC:setTextForeground(DC,{50,50,100,255})
 
277
    end,
 
278
    wxDC:setFont(DC,F),
 
279
    CH = (TBox - wxDC:getCharHeight(DC)) div 2,
 
280
    CW = (TBox - wxDC:getCharWidth(DC)) div 2,
 
281
    wxDC:drawText(DC, integer_to_list(Num), {X+CW,Y+CH+1}),
 
282
    ok.
 
283
 
 
284
get_coords(Sz,R,C) ->
 
285
    TBox = Sz div 3,
 
286
    R1 = R div 3,
 
287
    R2 = R rem 3,
 
288
    C1 = C div 3,
 
289
    C2 = C rem 3,
 
290
    {?BRD + C1*Sz + C2*TBox,
 
291
     ?BRD + R1*Sz + R2*TBox}.
 
292
 
 
293
draw_board(DC,{W0,H0},#state{pen=Pen}) ->
 
294
    BoxSz = getGeomSz(W0,H0),
 
295
    BS = ?BRD+3*BoxSz,
 
296
 
 
297
    wxPen:setWidth(Pen, 3),
 
298
    wxPen:setColour(Pen, {0,0,0}),
 
299
    wxDC:setPen(DC,Pen),
 
300
    
 
301
    wxDC:drawRoundedRectangle(DC, {?BRD,?BRD,3*BoxSz+1,3*BoxSz+1}, 
 
302
                              float(?ARC_R)),
 
303
    %% Testing DrawLines
 
304
    wxDC:drawLines(DC, [{?BRD+BoxSz, ?BRD}, {?BRD+BoxSz, BS}]),
 
305
    wxDC:drawLine(DC, {?BRD+BoxSz*2, ?BRD}, {?BRD+BoxSz*2, BS}),
 
306
    wxDC:drawLine(DC, {?BRD, ?BRD+BoxSz}, {BS, ?BRD+BoxSz}),
 
307
    wxDC:drawLine(DC, {?BRD, ?BRD+BoxSz*2}, {BS, ?BRD+BoxSz*2}),
 
308
 
 
309
    %% Draw inside lines
 
310
    wxPen:setWidth(Pen, 1),
 
311
    wxDC:setPen(DC,Pen),
 
312
    TBox = BoxSz div 3,   
 
313
    wxDC:drawLine(DC, {?BRD+TBox, ?BRD}, {?BRD+TBox, BS}),
 
314
    wxDC:drawLine(DC, {?BRD+TBox*2, ?BRD}, {?BRD+TBox*2, BS}),
 
315
    wxDC:drawLine(DC, {?BRD+TBox+BoxSz, ?BRD}, {?BRD+TBox+BoxSz, BS}),
 
316
    wxDC:drawLine(DC, {?BRD+TBox*2+BoxSz, ?BRD}, {?BRD+TBox*2+BoxSz, BS}),
 
317
    wxDC:drawLine(DC, {?BRD+TBox+BoxSz*2, ?BRD}, {?BRD+TBox+BoxSz*2, BS}),
 
318
    wxDC:drawLine(DC, {?BRD+TBox*2+BoxSz*2, ?BRD}, {?BRD+TBox*2+BoxSz*2, BS}),
 
319
    %% Vert
 
320
    wxDC:drawLine(DC, {?BRD, ?BRD+TBox}, {BS, ?BRD+TBox}),
 
321
    wxDC:drawLine(DC, {?BRD, ?BRD+TBox*2}, {BS, ?BRD+TBox*2}),
 
322
    wxDC:drawLine(DC, {?BRD, ?BRD+TBox+BoxSz}, {BS, ?BRD+TBox+BoxSz}),
 
323
    wxDC:drawLine(DC, {?BRD, ?BRD+TBox*2+BoxSz}, {BS, ?BRD+TBox*2+BoxSz}),
 
324
    wxDC:drawLine(DC, {?BRD, ?BRD+TBox+BoxSz*2}, {BS, ?BRD+TBox+BoxSz*2}),
 
325
    wxDC:drawLine(DC, {?BRD, ?BRD+TBox*2+BoxSz*2}, {BS, ?BRD+TBox*2+BoxSz*2}),
 
326
    BoxSz.
 
327
 
 
328
getGeomSz(W,H) ->
 
329
    Small = if W < H -> W; true -> H end,
 
330
    (Small - 2*?BRD) div 3.
 
331
 
 
332
 
 
333
%% popupmenu
 
334
 
 
335
create_popup_menu(GFX,Butt,X,Y,Frame) ->
 
336
    Port = wx:get_env(),
 
337
    spawn_link(fun() -> create_popup_menu1(GFX,Butt,Port,X,Y,Frame) end).
 
338
 
 
339
create_popup_menu1(GFX,Butt,Port,X,Y,Frame) ->
 
340
    wx:set_env(Port),
 
341
    PopupMenu = wxMenu:new(),
 
342
    create_popup_menu2(1, PopupMenu),
 
343
 
 
344
    wxEvtHandler:connect(PopupMenu, command_menu_selected),
 
345
    wxWindow:popupMenu(Frame,PopupMenu,X,Y),
 
346
    receive 
 
347
        #wx{event=#wxCommand{type=command_menu_selected},id=What} ->
 
348
            GFX ! {set_val,Butt,What}
 
349
    end.
 
350
 
 
351
create_popup_menu2(N,PP) when N > 9 ->
 
352
    wxMenu:append(PP, 0, "Clear");
 
353
create_popup_menu2(N,PP) ->
 
354
    wxMenu:append(PP, N,integer_to_list(N)),
 
355
    create_popup_menu2(N+1,PP).
 
356