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

« back to all changes in this revision

Viewing changes to lib/gs/contribs/othello/othello_board.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
108
108
 
109
109
loop(User,GamePid,Shell,Wids,Options) ->
110
110
    receive
111
 
        {gs,ButtId, click,ButtId1,[Button]} ->
 
111
        {gs,ButtId, click,_ButtId1,[Button]} ->
112
112
            GamePid1 = but_pressed(Button,ButtId,User,GamePid,Shell,
113
113
                                   Wids,Options),
114
114
            loop(User,GamePid1,Shell,Wids,Options);
115
115
 
116
 
        {gs,_, click,_,[MenuItem,MenuIndex]} ->
 
116
        {gs,_, click,_,[MenuItem,_MenuIndex]} ->
117
117
            Ops = menu_selected(MenuItem,User,GamePid,Wids,Options),
118
118
            loop(User,GamePid,Shell,Wids,Ops);
119
119
 
127
127
            game_msg(GameMsg,User,GamePid,Shell,Wids,Options)
128
128
    end.
129
129
 
130
 
but_pressed("Quit",ButtId,User,GamePid,Shell,Wids,Op) ->
 
130
but_pressed("Quit",_ButtId,_User,_GamePid,_Shell,_Wids,_Op) ->
131
131
    stop(),
132
132
    exit(quit);
133
 
but_pressed("Rules",ButtId,User,GamePid,Shell,Wids,Op) ->
 
133
but_pressed("Rules",_ButtId,_User,GamePid,_Shell,_Wids,_Op) ->
134
134
    io:format("No rules, do as you wish~n",[]),
135
135
    GamePid;
136
 
but_pressed("Help",ButtId,User,GamePid,Shell,Wids,Op) ->
 
136
but_pressed("Help",_ButtId,_User,GamePid,_Shell,_Wids,_Op) ->
137
137
    io:format("Othello game~n",[]),
138
138
    io:format("------------~n",[]),
139
139
    io:format("  Put markers by clicking in squares~n",[]),
141
141
    io:format("  Change colour by clicking on it~n",[]),
142
142
    io:format("~n",[]),
143
143
    GamePid;
144
 
but_pressed("Newgame",ButtId,User,GamePid,Shell,Wids,Options) ->
 
144
but_pressed("Newgame",_ButtId,_User,GamePid,_Shell,Wids,Options) ->
145
145
    new_game(GamePid,Wids,Options);
146
 
but_pressed([],ButtId,User,GamePid,Shell,Wids,Op) 
 
146
but_pressed([],ButtId,User,GamePid,_Shell,_Wids,_Op) 
147
147
                                        when pid(GamePid),User == player ->
148
148
    [C,R] = atom_to_list(ButtId),
149
149
    GamePid ! {self(),position,othello_adt:pos(C-96,translate(R-48))},
150
150
    GamePid;
151
 
but_pressed([],ButtId,User,GamePid,Shell,Wids,Op) ->
 
151
but_pressed([],ButtId,_User,GamePid,_Shell,_Wids,_Op) ->
152
152
    [C,R] = atom_to_list(ButtId),
153
153
    beep(othello_adt:pos(C-96,translate(R-48))),
154
154
    GamePid;
155
 
but_pressed(Button,ButtId,User,GamePid,Shell,Wids,Op) ->
 
155
but_pressed(Button,ButtId,_User,GamePid,_Shell,_Wids,_Op) ->
156
156
    io:format('Not implemented button pressed ~p, ~p!!!~n',[ButtId,Button]),
157
157
    GamePid.
158
158
 
159
 
menu_selected("Black",User,GamePid,Wids,Options) ->
160
 
    Op0 = setelement(1,Options,white),
161
 
    Op1 = setelement(2,Op0,white),
162
 
    write_options(Op1,Wids),
163
 
    Op1;
164
 
menu_selected("White",User,GamePid,Wids,Options) ->
165
 
    Op0 = setelement(1,Options,black),
166
 
    Op1 = setelement(2,Op0,black),
167
 
    write_options(Op1,Wids),
168
 
    Op1;
169
 
menu_selected("Black (begin)",User,GamePid,Wids,Options) ->
170
 
    Op0 = setelement(1,Options,white),
171
 
    Op1 = setelement(2,Op0,black),
172
 
    write_options(Op1,Wids),
173
 
    Op1;
174
 
menu_selected("White (begin)",User,GamePid,Wids,Options) ->
175
 
    Op0 = setelement(1,Options,black),
176
 
    Op1 = setelement(2,Op0,white),
177
 
    write_options(Op1,Wids),
178
 
    Op1;
179
 
menu_selected("Beginner",User,GamePid,Wids,Options) ->
 
159
menu_selected("Black",_User,_GamePid,Wids,Options) ->
 
160
    Op0 = setelement(1,Options,white),
 
161
    Op1 = setelement(2,Op0,white),
 
162
    write_options(Op1,Wids),
 
163
    Op1;
 
164
menu_selected("White",_User,_GamePid,Wids,Options) ->
 
165
    Op0 = setelement(1,Options,black),
 
166
    Op1 = setelement(2,Op0,black),
 
167
    write_options(Op1,Wids),
 
168
    Op1;
 
169
menu_selected("Black (begin)",_User,_GamePid,Wids,Options) ->
 
170
    Op0 = setelement(1,Options,white),
 
171
    Op1 = setelement(2,Op0,black),
 
172
    write_options(Op1,Wids),
 
173
    Op1;
 
174
menu_selected("White (begin)",_User,_GamePid,Wids,Options) ->
 
175
    Op0 = setelement(1,Options,black),
 
176
    Op1 = setelement(2,Op0,white),
 
177
    write_options(Op1,Wids),
 
178
    Op1;
 
179
menu_selected("Beginner",_User,_GamePid,Wids,Options) ->
180
180
    Op1 = setelement(3,Options,1),
181
181
    write_options(Op1,Wids),
182
182
    Op1;
183
 
menu_selected("Intermediate",User,GamePid,Wids,Options) ->
 
183
menu_selected("Intermediate",_User,_GamePid,Wids,Options) ->
184
184
    Op1 = setelement(3,Options,2),
185
185
    write_options(Op1,Wids),
186
186
    Op1;
187
 
menu_selected("Advanced",User,GamePid,Wids,Options) ->
 
187
menu_selected("Advanced",_User,_GamePid,Wids,Options) ->
188
188
    Op1 = setelement(3,Options,3),
189
189
    write_options(Op1,Wids),
190
190
    Op1;
191
 
menu_selected("Expert",User,GamePid,Wids,Options) ->
 
191
menu_selected("Expert",_User,_GamePid,Wids,Options) ->
192
192
    Op1 = setelement(3,Options,4),
193
193
    write_options(Op1,Wids),
194
194
    Op1;
195
 
menu_selected(What,User,GamePid,Wids,Options) ->
 
195
menu_selected(What,_User,_GamePid,_Wids,Options) ->
196
196
    io:format('Menu item not implemented <~s>~n',[What]),
197
197
    Options.
198
198
 
212
212
            GamePid ! {self(),go_on_play},
213
213
            loop(computer,GamePid,Shell,Wids,Options);
214
214
 
215
 
        {GamePid,player,Computer,Player} ->
 
215
        {GamePid,player,_Computer,Player} ->
216
216
            show_player(element(1,Wids),Player),
217
217
            cursor("top_left_arrow"),
218
218
            GamePid ! {self(),go_on_play},
246
246
new_game(_,Wids,Options) ->
247
247
    new_game(Wids,Options).
248
248
 
249
 
new_game(Wids,Options) ->
 
249
new_game(_Wids,Options) ->
250
250
    label("",lastdraw),
251
251
    Computer = element(1,Options),
252
252
    Start = element(2,Options),
267
267
    Button = get(Name),
268
268
    bell(Button).
269
269
 
270
 
show_player(Status,white) ->
 
270
show_player(_Status,white) ->
271
271
    label("White to draw",todraw);
272
 
show_player(Status,black) ->
 
272
show_player(_Status,black) ->
273
273
    label("Black to draw",todraw).
274
274
 
275
 
write_score(Wids,WhiteRes,BlackRes) ->
 
275
write_score(_Wids,WhiteRes,BlackRes) ->
276
276
    label(integer_to_list(BlackRes),bscore),
277
277
    label(integer_to_list(WhiteRes),wscore).
278
278
 
279
 
write_draw(Wids,Draw) ->
 
279
write_draw(_Wids,Draw) ->
280
280
    Col = othello_adt:col(Draw),
281
281
    Row = othello_adt:row(Draw),
282
282
    label(lists:flatten(io_lib:format('{~w,~w}',[Col,Row])), lastdraw).
288
288
write_colour(Options,Wids) ->
289
289
    write_colour(element(1,Options),element(2,Options),Wids).
290
290
 
291
 
write_colour(black,white,Wids) -> label("White (begin)",colour);
292
 
write_colour(black,black,Wids) -> label("White",colour);
293
 
write_colour(white,black,Wids) -> label("Black (begin)",colour);
294
 
write_colour(white,white,Wids) -> label("Black",colour).
 
291
write_colour(black,white,_Wids) -> label("White (begin)",colour);
 
292
write_colour(black,black,_Wids) -> label("White",colour);
 
293
write_colour(white,black,_Wids) -> label("Black (begin)",colour);
 
294
write_colour(white,white,_Wids) -> label("Black",colour).
295
295
    
296
 
write_level(Options,Wids) ->
 
296
write_level(Options,_Wids) ->
297
297
    case element(3,Options) of
298
298
        1 -> label("Beginner",level);
299
299
        2 -> label("Intermediate",level);
301
301
        4 -> label("Expert",level)
302
302
    end.
303
303
 
304
 
cursor(What) ->
 
304
cursor(_What) ->
305
305
    done.
306
306
%cursor(What) -> cursor(get(),What).
307
307