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

« back to all changes in this revision

Viewing changes to lib/gs/contribs/bonk/bonk.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:
63
63
 
64
64
idle(SoundPid, SqrPids, Bmps, Colors) ->
65
65
    receive
66
 
        {gs, newButton, click, Data, Args} ->
 
66
        {gs, newButton, click, _Data, _Args} ->
67
67
            init(SoundPid, SqrPids, Bmps, Colors);
68
 
        {gs, aboutButton, click, Data, Args} ->
 
68
        {gs, aboutButton, click, _Data, _Args} ->
69
69
            display_about(),
70
70
            idle(SoundPid, SqrPids, Bmps, Colors);
71
 
        {gs, quitButton, click, Data, Args} ->
 
71
        {gs, quitButton, click, _Data, _Args} ->
72
72
            SoundPid ! quit,
73
73
            send_to_all(SqrPids, quit);
74
 
        Other ->
75
 
            %%io:format("Got ~w in idle~n", [Other]),
 
74
        _Other ->
 
75
            %%io:format("Got ~w in idle~n", [_Other]),
76
76
            idle(SoundPid, SqrPids, Bmps, Colors)
77
77
    end.
78
78
 
93
93
 
94
94
game(SoundPid, SqrPids, Bmps, Colors, Scores) ->
95
95
    receive
96
 
        {gs, Square, buttonpress, SqrPid, [1 | Rest]} when pid(SqrPid) ->
 
96
        {gs, _Square, buttonpress, SqrPid, [1 | _Rest]} when pid(SqrPid) ->
97
97
            SqrPid ! bonk,
98
98
            game(SoundPid, SqrPids, Bmps, Colors, Scores);
99
 
        {gs, _Id, buttonpress, _Data, [Butt | Rest]} when Butt =/= 1 ->
 
99
        {gs, _Id, buttonpress, _Data, [Butt | _Rest]} when Butt =/= 1 ->
100
100
            NewScores = bomb(SoundPid, SqrPids, Scores),
101
101
            game(SoundPid, SqrPids, Bmps, Colors, NewScores);
102
102
        {show, Square, Rect} ->
118
118
        {bombed, Square, Rect} ->
119
119
            NewScores = bombed(SoundPid, SqrPids, Square, Rect, Scores, Colors),
120
120
            game(SoundPid, SqrPids, Bmps, Colors, NewScores);
121
 
        {gs, endButton, click, Data, Args} ->
 
121
        {gs, endButton, click, _Data, _Args} ->
122
122
            game_over(SoundPid, SqrPids, Bmps, Colors, Scores);
123
 
        {gs, quitButton, click, Data, Args} ->
 
123
        {gs, quitButton, click, _Data, _Args} ->
124
124
            quit(SoundPid, SqrPids, Bmps, Colors, Scores);
125
 
        Other ->
 
125
        _Other ->
126
126
            game(SoundPid, SqrPids, Bmps, Colors, Scores)
127
127
    end.
128
128
            
140
140
    idle(SoundPid, SqrPids, Bmps, Colors).
141
141
 
142
142
 
143
 
quit(SoundPid, SqrPids, Bmps, Colors, Scores) ->
 
143
quit(SoundPid, SqrPids, _Bmps, _Colors, _Scores) ->
144
144
    SoundPid ! quit,
145
145
    send_to_all(SqrPids, quit),
146
146
    true.
154
154
            SoundPid ! bomb,
155
155
            gs:config(bombOut,[{text,integer_to_list(Bombs-1)}]),
156
156
            Scores#scores{bombs=Bombs-1};
157
 
        Other ->
 
157
        _Other ->
158
158
            Scores
159
159
    end.
160
160
 
171
171
            Scores#scores{showed=Showed+1}
172
172
    end.
173
173
    
174
 
hide_face(Square, Rect, Colors, Scores) ->
 
174
hide_face(_Square, Rect, _Colors, Scores) ->
175
175
    Showed = Scores#scores.showed,
176
176
    gs:config(Rect, [{bitmap,lists:append(bonk_dir(),"bitmaps/bonktom")}]),
177
177
    Scores#scores{showed=Showed-1}.
178
178
 
179
179
 
180
 
miss_face(SoundPid, Square, Rect, Colors, Scores) ->
 
180
miss_face(SoundPid, _Square, Rect, Colors, Scores) ->
181
181
    SoundPid ! missed,
182
182
    gs:config(Rect, [{bitmap,lists:append(bonk_dir(),"bitmaps/bonkmiss")}, {fg, Colors#colors.miss}]),
183
183
    Bonus = Scores#scores.bonus,
190
190
            {game_over, Scores}
191
191
    end.
192
192
 
193
 
bonked(SoundPid, SqrPids, Square, Rect, Scores, Colors) ->
 
193
bonked(SoundPid, SqrPids, _Square, Rect, Scores, Colors) ->
194
194
    gs:config(Rect, [{bitmap,lists:append(bonk_dir(),"bitmaps/bonkx")}, {fg, Colors#colors.x}]),
195
195
    SoundPid ! bonk,
196
196
    update_score(SoundPid, SqrPids, Scores).
197
197
 
198
 
bombed(SoundPid, SqrPids, Square, Rect, Scores, Colors) ->
 
198
bombed(SoundPid, SqrPids, _Square, Rect, Scores, Colors) ->
199
199
    gs:config(Rect, [{bitmap,lists:append(bonk_dir(),"bitmaps/bonkbomb")}, {fg, Colors#colors.bomb}]),
200
200
    update_score(SoundPid, SqrPids, Scores).
201
201
 
219
219
    end.
220
220
            
221
221
 
222
 
send_to_all([],Msg) ->
 
222
send_to_all([], _Msg) ->
223
223
    true;
224
224
 
225
225
send_to_all([Pid|Rest],Msg) when pid(Pid) ->
226
226
    Pid ! Msg,
227
227
    send_to_all(Rest,Msg);
228
228
 
229
 
send_to_all([Else|Rest],Msg) ->
 
229
send_to_all([_Else|Rest],Msg) ->
230
230
    send_to_all(Rest,Msg).
231
231
 
232
232
 
268
268
    DSX = TextWidth+94,        % pixels between status items
269
269
    SY = SLineY+2,             % y-pos status items
270
270
    HiWidth = 100,             % width of high score field
271
 
    HiHeight = 180,            % height of the same
 
271
    _HiHeight = 180,            % height of the same
272
272
    HiX = Width-HiWidth,       % high score text position
273
273
    HiY = BLineY+10,
274
274
    DHY = 20,                  % space between title & scores
389
389
    create_squares(X, Y, Size, Color, Spc, 1, 1, [], []).
390
390
 
391
391
 
392
 
create_squares(X, Y, Size, Color, Spc, 4, 5, Pids, Bmps) ->
 
392
create_squares(_X, _Y, _Size, _Color, _Spc, 4, 5, Pids, Bmps) ->
393
393
    {Pids, Bmps};
394
394
 
395
395
create_squares(X, Y, Size, Color, Spc, Row, 5, Pids, Bmps) ->
467
467
    end.
468
468
 
469
469
 
470
 
update_scorelist_2([], Score, N, SoundPid) when N < 10 ->
 
470
update_scorelist_2([], Score, N, _SoundPid) when N < 10 ->
471
471
    [[integer_to_list(Score),getuser()]];
472
472
 
473
 
update_scorelist_2(_, _, N, SoundPid) when N >= 10 ->
 
473
update_scorelist_2(_, _, N, _SoundPid) when N >= 10 ->
474
474
    [];
475
475
 
476
476
update_scorelist_2([[Sc, Name] | Rest], Score, N, SoundPid) ->
482
482
            end,
483
483
            lists:append([[integer_to_list(Score),getuser()]],
484
484
                         update_scorelist_3([[Sc,Name]|Rest],N+1));
485
 
        Other ->
 
485
        _Other ->
486
486
            lists:append([[Sc,Name]],update_scorelist_2(Rest, Score, N+1, SoundPid))
487
487
    end.
488
488
 
521
521
 
522
522
flush() ->
523
523
    receive
524
 
        X ->
 
524
        _X ->
525
525
            flush()
526
526
        after
527
527
            0 ->
560
560
        {ok, Fd} ->
561
561
            write_text(Fd, "", io:get_line(Fd, "")),
562
562
            file:close(Fd);
563
 
        {error, Reason} ->
 
563
        {error, _Reason} ->
564
564
            gs:config(aboutText, {text, "Error: could not read the about file"})
565
565
    end,
566
566
 
570
570
            gs:destroy(aboutWin)
571
571
    end.
572
572
 
573
 
write_text(Fd, Text, eof) ->
 
573
write_text(_Fd, Text, eof) ->
574
574
    gs:config(aboutText, {text, Text});
575
575
write_text(Fd, Text, More) ->
576
576
    write_text(Fd, lists:append(Text, More), io:get_line(Fd, "")).