DEADSOFTWARE

opengl: rebind texture only when needed
[flatwaifu.git] / src / gl / render.c
1 #include "glob.h"
2 #include "render.h"
3 #include "files.h"
4 #include "memory.h"
5 #include "misc.h"
6 #include "error.h"
8 #include "menu.h"
9 #include "game.h"
10 #include "dots.h"
11 #include "items.h"
13 #include "sound.h" // snd_vol
14 #include "music.h" // mus_vol
16 #include "fx.h"
17 #include "player.h"
18 #include "monster.h"
19 #include "weapons.h"
20 #include "smoke.h"
21 #include "view.h"
22 #include "switch.h" // sw_secrets
24 #ifdef __APPLE__
25 # include <OpenGL/gl.h>
26 #else
27 # include <GL/gl.h>
28 #endif
29 #include <stdlib.h> // malloc free abs
30 #include <assert.h> // assert
31 #include <SDL.h>
33 #define VGA_TRANSPARENT_COLOR 0
34 #define DEFAULT_SKY_COLOR 0x97
35 #define MANCOLOR 0xD0
36 #define PLAYER_COLOR_OFFSET 7
37 #define MAXAIR 1091
38 #define ANIT 5
39 #define PL_FLASH 90
41 #pragma pack(1)
42 typedef struct vgaimg {
43 word w, h;
44 short x, y;
45 byte data[];
46 } vgaimg;
48 typedef struct rgb {
49 byte r, g, b;
50 } rgb;
52 typedef struct rgba {
53 byte r, g, b, a;
54 } rgba;
55 #pragma pack()
57 typedef struct node {
58 struct cache *base;
59 struct node *left, *right;
60 int l, t, r, b;
61 int leaf;
62 } node;
64 typedef struct cache {
65 struct cache *next;
66 struct node root;
67 GLuint id;
68 } cache;
70 typedef struct image {
71 node *n;
72 GLint x, y;
73 GLuint w, h;
74 int res;
75 } image;
77 /* Render Specific */
78 int SCRW = 320; // public
79 int SCRH = 200; // public
80 static int gamma;
81 static int fullscreen;
82 static SDL_Surface *surf;
83 static rgb playpal[256];
84 static byte bright[256];
85 static GLuint lastTexture;
86 static cache *root;
88 /* Game */
89 static image scrnh[3]; // TITLEPIC INTERPIC ENDPIC
90 static image ltn[2][2];
92 /* Smoke */
93 static image smk_spr[SMSN];
94 static image smk_fspr[FLSN];
96 /* Effects */
97 static image fx_spr[15];
98 static char fx_sprd[15];
100 /* Weapons */
101 static image wp_spr[49*2];
102 static char wp_sprd[49*2];
104 /* Items */
105 static image item_spr[58];
106 static char item_sprd[58];
108 /* Player */
109 static image plr_spr[27*2];
110 static image plr_msk[27*2];
111 static char plr_sprd[27*2];
112 static image plr_wpn[11][6];
114 /* Monsters */
115 static image pl_spr[2];
116 static image pl_msk[2];
117 static image mn_spr[MN_TN][29*2];
118 static image mn_man_msk[29*2];
119 static char mn_sprd[MN_TN][29*2];
120 static image mn_fspr[8];
121 static image mn_sgun[2];
123 /* Misc */
124 static image sth[22];
125 static image bfh[160 - '!'];
126 static image sfh[160 - '!'];
127 static image stone;
128 static image stone2;
129 static image keys[3];
130 static int prx = 0;
131 static int pry = 0;
133 /* Menu */
134 static int gm_tm;
135 static image msklh[2];
136 static image mbarl;
137 static image mbarm;
138 static image mbarr;
139 static image mbaro;
140 static image mslotl;
141 static image mslotm;
142 static image mslotr;
144 /* Map */
145 static const char *anm[ANIT - 1][5] = {
146 {"WALL22_1", "WALL23_1", "WALL23_2", NULL, NULL},
147 {"WALL58_1", "WALL58_2", "WALL58_3", NULL, NULL},
148 {"W73A_1", "W73A_2", NULL, NULL, NULL},
149 {"RP2_1", "RP2_2", "RP2_3", "RP2_4", NULL}
150 };
151 static int max_wall_width;
152 static int max_wall_height;
153 static int max_textures;
154 static image walp[256];
155 static byte walani[256];
156 static image anip[ANIT][5];
157 static byte anic[ANIT];
158 static image horiz;
160 /* Texture cache */
162 // https://blackpawn.com/texts/lightmaps/
163 static node *R_node_alloc (node *p, int w, int h) {
164 assert(p);
165 assert(w > 0);
166 assert(h > 0);
167 if (p->left) {
168 assert(p->right);
169 node *n = R_node_alloc(p->left, w, h);
170 return n ? n : R_node_alloc(p->right, w, h);
171 } else {
172 int pw = p->r - p->l + 1;
173 int ph = p->b - p->t + 1;
174 if (p->leaf || pw < w || ph < h) {
175 return NULL;
176 } else if (pw == w && ph == h) {
177 p->leaf = 1;
178 return p;
179 } else {
180 p->left = malloc(sizeof(node));
181 p->right = malloc(sizeof(node));
182 if (pw - w > ph - h) {
183 *p->left = (node) {
184 .l = p->l,
185 .t = p->t,
186 .r = p->l + w - 1,
187 .b = p->b
188 };
189 *p->right = (node) {
190 .l = p->l + w,
191 .t = p->t,
192 .r = p->r,
193 .b = p->b
194 };
195 } else {
196 *p->left = (node) {
197 .l = p->l,
198 .t = p->t,
199 .r = p->r,
200 .b = p->t + h - 1
201 };
202 *p->right = (node) {
203 .l = p->l,
204 .t = p->t + h,
205 .r = p->r,
206 .b = p->b
207 };
209 return R_node_alloc(p->left, w, h);
214 static void R_gl_bind_texture (GLuint id) {
215 if (id != lastTexture) {
216 glBindTexture(GL_TEXTURE_2D, id);
220 static cache *R_cache_new (void) {
221 GLuint id = 0;
222 GLint size = 0;
223 cache *c = NULL;
224 glGetIntegerv(GL_MAX_TEXTURE_SIZE, &size);
225 size = size < 512 ? size : 512; // more can be buggy on older hardware
226 if (size) {
227 glGenTextures(1, &id);
228 if (id) {
229 R_gl_bind_texture(id);
230 glTexParameteri(GL_TEXTURE_2D, GL_TEXTURE_MIN_FILTER, GL_NEAREST);
231 glTexParameteri(GL_TEXTURE_2D, GL_TEXTURE_MAG_FILTER, GL_NEAREST);
232 glTexImage2D(GL_TEXTURE_2D, 0, GL_RGBA, size, size, 0, GL_RGBA, GL_UNSIGNED_BYTE, NULL);
233 c = malloc(sizeof(cache));
234 if (c != NULL) {
235 *c = (cache) {
236 .id = id,
237 .root.r = size - 1,
238 .root.b = size - 1
239 };
240 } else {
241 glDeleteTextures(1, &id);
245 //logo("new cache %p\n", c);
246 return c;
249 static node *R_cache_alloc (cache *root, int w, int h) {
250 assert(root);
251 assert(w > 0 && h > 0);
252 node *n = NULL;
253 cache *p = NULL;
254 cache *c = root;
255 while (c && !n) {
256 n = R_node_alloc(&c->root, w, h);
257 if (n) {
258 n->base = c;
260 p = c;
261 c = c->next;
263 if (!n) {
264 c = R_cache_new();
265 if (c) {
266 p->next = c;
267 n = R_node_alloc(&c->root, w, h);
268 if (n) {
269 n->base = c;
273 return n;
276 static void R_cache_update (node *n, const void *data, int w, int h) {
277 assert(n);
278 assert(n->base);
279 assert(data);
280 int nw = n->r - n->l + 1;
281 int nh = n->b - n->t + 1;
282 assert(w == nw);
283 assert(h == nh);
284 R_gl_bind_texture(n->base->id);
285 glTexSubImage2D(GL_TEXTURE_2D, 0, n->l, n->t, nw, nh, GL_RGBA, GL_UNSIGNED_BYTE, data);
288 /* Generic helpers */
290 static void R_init_playpal (void) {
291 int i;
292 byte *vgapal = M_lock(F_getresid("PLAYPAL"));
293 for (i = 0; i < 256; i++) {
294 playpal[i] = (rgb) {
295 .r = vgapal[i * 3 + 0] * 255 / 63,
296 .g = vgapal[i * 3 + 1] * 255 / 63,
297 .b = vgapal[i * 3 + 2] * 255 / 63,
298 };
299 bright[i] = ((int)vgapal[i * 3 + 0] + vgapal[i * 3 + 1] + vgapal[i * 3 + 2]) * 8 / (63 * 3);
301 M_unlock(vgapal);
304 static vgaimg *R_getvga (int id) {
305 int loaded = M_was_locked(id);
306 vgaimg *v = M_lock(id);
307 if (v != NULL && !loaded) {
308 v->w = short2host(v->w);
309 v->h = short2host(v->h);
310 v->x = short2host(v->x);
311 v->y = short2host(v->y);
313 return v;
316 static rgba *R_extract_flame_spr (vgaimg *v) {
317 static const byte flametab[16] = {
318 0xBC, 0xBA, 0xB8, 0xB6, 0xB4, 0xB2, 0xB0, 0xD5,
319 0xD6, 0xD7, 0xA1, 0xA0, 0xE3, 0xE2, 0xE1, 0xE0
320 };
321 int i, j;
322 rgba *s = malloc(v->w * v->h * sizeof(rgba));
323 if (s != NULL) {
324 for (j = 0; j < v->h; j++) {
325 for (i = 0; i < v->w; i++) {
326 int k = j * v->w + i;
327 byte c = v->data[k] + bright[DEFAULT_SKY_COLOR];
328 s[k] = (rgba) {
329 .r = playpal[flametab[c]].r,
330 .g = playpal[flametab[c]].g,
331 .b = playpal[flametab[c]].b,
332 .a = v->data[k] == VGA_TRANSPARENT_COLOR ? 0x00 : 0xFF,
333 };
337 return s;
340 static rgba *R_extract_smoke_spr (vgaimg *v) {
341 int i, j;
342 rgba *s = malloc(v->w * v->h * sizeof(rgba));
343 if (s != NULL) {
344 for (j = 0; j < v->h; j++) {
345 for (i = 0; i < v->w; i++) {
346 int k = j * v->w + i;
347 byte c = ((v->data[k] + bright[DEFAULT_SKY_COLOR]) + 0x60) ^ 0x0F;
348 byte a = 0xFF - ((int)playpal[c].r + playpal[c].g + playpal[c].b) / 3;
349 s[k] = (rgba) {
350 .r = playpal[c].r,
351 .g = playpal[c].g,
352 .b = playpal[c].b,
353 .a = v->data[k] == VGA_TRANSPARENT_COLOR ? 0x00 : a,
354 };
358 return s;
361 static rgba *R_extract_mask_spr (vgaimg *v) {
362 int i, j;
363 rgba *s = malloc(v->w * v->h * sizeof(rgba));
364 if (s != NULL) {
365 for (j = 0; j < v->h; j++) {
366 for (i = 0; i < v->w; i++) {
367 int k = j * v->w + i;
368 byte c = v->data[k];
369 if (c >= 0x70 && c <= 0x7F) {
370 byte mask = c - 0x70;
371 mask = 0xFF - ((mask << 4) | mask);
372 s[k] = (rgba) {
373 .r = mask,
374 .g = mask,
375 .b = mask,
376 .a = 0xFF,
377 };
378 } else {
379 s[k] = (rgba) {
380 .r = 0,
381 .g = 0,
382 .b = 0,
383 .a = 0,
384 };
389 return s;
392 static rgba *R_extract_rgba_spr (vgaimg *v) {
393 int i, j;
394 rgba *s = malloc(v->w * v->h * sizeof(rgba));
395 if (s != NULL) {
396 for (j = 0; j < v->h; j++) {
397 for (i = 0; i < v->w; i++) {
398 int k = j * v->w + i;
399 byte c = v->data[k];
400 s[k] = (rgba) {
401 .r = playpal[c].r,
402 .g = playpal[c].g,
403 .b = playpal[c].b,
404 .a = c == VGA_TRANSPARENT_COLOR ? 0x00 : 0xFF,
405 };
409 return s;
412 /* OpenGL helpers */
414 static image R_gl_create_image (const rgba *buf, int w, int h) {
415 node *n = R_cache_alloc(root, w, h);
416 if (n) {
417 R_cache_update(n, buf, w, h);
419 return (image) {
420 .n = n,
421 .w = w,
422 .h = h,
423 .res = -1
424 };
427 static image R_gl_get_special_image (int id, rgba *(*fn)(vgaimg*)) {
428 image img;
429 vgaimg *v = R_getvga(id);
430 if (v != NULL) {
431 rgba *buf = (*fn)(v);
432 img = R_gl_create_image(buf, v->w, v->h);
433 img.x = v->x;
434 img.y = v->y;
435 img.res = id;
436 M_unlock(v);
437 free(buf);
438 } else {
439 img = (image) {
440 .res = id
441 };
443 return img;
446 static image R_gl_getimage (int id) {
447 return R_gl_get_special_image(id, &R_extract_rgba_spr);
450 static image R_gl_loadimage (const char name[8]) {
451 return R_gl_getimage(F_getresid(name));
454 static image R_gl_get_special_spr (const char n[4], int s, int d, rgba *(*fn)(vgaimg*)) {
455 return R_gl_get_special_image(F_getsprid(n, s, d), fn);
458 static void R_gl_free_image (image *img) {
459 if (img->n != NULL && img->res >= 0) {
460 // TODO delete node
462 img->n = NULL;
465 static void R_gl_draw_quad (int x, int y, int w, int h) {
466 glBegin(GL_QUADS);
467 glVertex2i(x + w, y);
468 glVertex2i(x, y);
469 glVertex2i(x, y + h);
470 glVertex2i(x + w, y + h);
471 glEnd();
474 static void R_gl_draw_textured (image *img, int x, int y, int w, int h, int flip) {
475 if (img->n) {
476 GLfloat nw = img->n->base->root.r + 1;
477 GLfloat nh = img->n->base->root.b + 1;
478 GLfloat ax = (flip ? img->n->l : img->n->r + 1) / nw;
479 GLfloat bx = (flip ? img->n->r + 1 : img->n->l) / nh;
480 GLfloat ay = (img->n->t) / nw;
481 GLfloat by = (img->n->b + 1) / nh;
482 R_gl_bind_texture(img->n->base->id);
483 glEnable(GL_TEXTURE_2D);
484 glBegin(GL_QUADS);
485 glTexCoord2f(ax, ay); glVertex2i(x + w, y);
486 glTexCoord2f(bx, ay); glVertex2i(x, y);
487 glTexCoord2f(bx, by); glVertex2i(x, y + h);
488 glTexCoord2f(ax, by); glVertex2i(x + w, y + h);
489 glEnd();
490 } else {
491 glColor3ub(255, 0, 0);
492 glDisable(GL_BLEND);
493 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
494 glDisable(GL_TEXTURE_2D);
495 R_gl_draw_quad(x, y, w, h);
499 /* fit image into rectangle without applying offset and transparency */
500 static void R_gl_draw_image_ext (image *img, int x, int y, int w, int h) {
501 glDisable(GL_BLEND);
502 glColor3ub(255, 255, 255);
503 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
504 R_gl_draw_textured(img, x, y, w, h, 0);
507 /* draw sprite with offset and coloring */
508 static void R_gl_draw_image_color (image *img, int x, int y, int flip) {
509 int xx = flip ? x - img->w + img->x : x - img->x;
510 glEnable(GL_BLEND);
511 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
512 R_gl_draw_textured(img, xx, y - img->y, img->w, img->h, flip);
515 /* draw sprite with offset */
516 static void R_gl_draw_image (image *img, int x, int y, int flip) {
517 glColor3ub(255, 255, 255);
518 R_gl_draw_image_color(img, x, y, flip);
521 static void R_gl_set_color (byte c) {
522 glColor3ub(playpal[c].r, playpal[c].g, playpal[c].b);
525 static void R_gl_setclip (int x, int y, int w, int h) {
526 glScissor(x, SCRH - h - y, w, h);
529 static void R_gl_setmatrix (void) {
530 glScissor(0, 0, SCRW, SCRH);
531 glViewport(0, 0, SCRW, SCRH);
532 glMatrixMode(GL_PROJECTION);
533 glLoadIdentity();
534 glOrtho(0, SCRW, SCRH, 0, 0, 1);
535 glMatrixMode(GL_MODELVIEW);
536 glLoadIdentity();
539 /* --- Misc --- */
541 static image Z_getspr (const char n[4], int s, int d, char *dir) {
542 int h = F_getsprid(n, s, d);
543 if (dir != NULL) {
544 *dir = (h & 0x8000) ? 1 : 0;
546 return R_gl_getimage(h);
549 static void Z_putch_generic (image img[], int off, int ch) {
550 image *p = NULL;
551 if (ch > 32 && ch < 160) {
552 p = &img[ch - '!'];
554 if (p != NULL) {
555 R_gl_draw_image(p, prx, pry, 0);
556 prx += p->w - 1;
557 } else {
558 prx += off;
562 static void Z_printf_generic (image img[], int off, const char *fmt, va_list ap) {
563 int i;
564 char buf[80];
565 vsprintf(buf, fmt, ap);
566 for (i = 0; buf[i]; ++i) {
567 switch (buf[i]) {
568 case '\n':
569 pry += off + 1;
570 case '\r':
571 prx = 0;
572 break;
573 default:
574 Z_putch_generic(img, off, (byte)buf[i]);
579 static void Z_gotoxy (int x, int y) {
580 prx = x;
581 pry = y;
584 static void Z_printbf (const char *fmt, ...) {
585 va_list a;
586 va_start(a, fmt);
587 Z_printf_generic(bfh, 12, fmt, a);
588 va_end(a);
591 static void Z_printsf (const char *fmt, ...) {
592 va_list a;
593 va_start(a, fmt);
594 Z_printf_generic(sfh, 7, fmt, a);
595 va_end(a);
598 static void Z_printhf (const char *fmt, ...) {
599 int i, c;
600 char buf[80];
601 va_list a;
602 va_start(a, fmt);
603 vsprintf(buf, fmt, a);
604 va_end(a);
605 for (i = 0; buf[i]; ++i) {
606 switch (buf[i]) {
607 case '0':
608 case '1':
609 case '2':
610 case '3':
611 case '4':
612 case '5':
613 case '6':
614 case '7':
615 case '8':
616 case '9':
617 c = buf[i] - '0';
618 break;
619 case '-':
620 c = 10;
621 break;
622 case '%':
623 c = 11;
624 break;
625 case '\n':
626 pry += 19;
627 case '\r':
628 c = -1;
629 prx = 0;
630 break;
631 default:
632 c = -1;
633 break;
635 if (c >= 0) {
636 R_gl_draw_image(&sth[c], prx, pry, 0);
638 prx += 14;
642 /* --- Menu --- */
644 static image *PL_getspr (int s, int d, int msk) {
645 int i = (s - 'A') * 2 + d;
646 return msk ? &plr_msk[i] : &plr_spr[i];
649 static void GM_draw (void) {
650 enum {MENU, MSG}; // copypasted from menu.c!
651 enum {
652 CANCEL, NEWGAME, LOADGAME, SAVEGAME, OPTIONS, QUITGAME, QUIT, ENDGAME, ENDGM,
653 PLR1, PLR2, COOP, DM, VOLUME, GAMMA, LOAD, SAVE, PLCOLOR, PLCEND, MUSIC, INTERP,
654 SVOLM, SVOLP, MVOLM, MVOLP, GAMMAM, GAMMAP, PL1CM, PL1CP, PL2CM, PL2CP
655 }; // copypasted from menu.c!
656 int i, j, k, x, y, cx, cy;
657 image *img;
658 gm_tm += 1;
659 if (mnu != NULL) {
660 cx = SCRW / 2;
661 cy = SCRH / 2;
662 if (mnu->type == MENU) {
663 y = cy - (mnu->n * 16 - 20) / 2;
664 Z_gotoxy(cx - mnu->x, y - 10); Z_printbf("%s", mnu->ttl);
665 for (i = 0; i < mnu->n; i++) {
666 if (mnu->t[i] == LOAD || mnu->t[i] == SAVE) {
667 j = y + i * 16 + 29;
668 R_gl_draw_image(&mslotl, cx - mnu->x, j, 0);
669 for (k = 8; k < 184; k += 8) {
670 R_gl_draw_image(&mslotm, cx - mnu->x + k, j, 0);
672 R_gl_draw_image(&mslotr, cx - mnu->x + 184, j, 0);
673 Z_gotoxy(cx - mnu->x + 4, j - 8);
674 if (input && i == save_mnu.cur) {
675 Z_printsf("%s_", ibuf);
676 } else {
677 Z_printsf("%s", savname[i]);
679 } else {
680 x = mnu->t[i] >= SVOLM ? (mnu->t[i] >= PL1CM ? 50 : 152) : 0;
681 Z_gotoxy(cx - mnu->x + x, y + i * 16 + 20);
682 Z_printbf("%s", mnu->m[i]);
683 switch (mnu->t[i]) {
684 case MUSIC:
685 Z_printbf(" '%s'", g_music);
686 break;
687 case INTERP:
688 Z_printbf("%s", fullscreen ? "ON" : "OFF");
689 break;
690 case PL1CM:
691 case PL1CP:
692 case PL2CM:
693 case PL2CP:
694 img = PL_getspr(*panimp, 0, 0);
695 R_gl_draw_image(img, cx - mnu->x + (mnu->t[i] == PL1CM ? 15 : 35), y + i * 16 + 20 + 14, 0);
696 img = PL_getspr(*panimp, 0, 1);
697 R_gl_set_color(pcolortab[(mnu->t[i] == PL1CM) ? p1color : p2color] + PLAYER_COLOR_OFFSET);
698 R_gl_draw_image_color(img, cx - mnu->x + (mnu->t[i] == PL1CM ? 15 : 35), y + i * 16 + 20 + 14, 0);
699 break;
700 case SVOLM:
701 case SVOLP:
702 case MVOLM:
703 case MVOLP:
704 case GAMMAM:
705 case GAMMAP:
706 j = y + i * 16 + 20;
707 R_gl_draw_image(&mbarl, cx - mnu->x, j, 0);
708 for (k = 8; k < 144; k += 8) {
709 R_gl_draw_image(&mbarm, cx - mnu->x + k, j, 0);
711 R_gl_draw_image(&mbarr, cx - mnu->x + 144, j, 0);
712 switch (mnu->t[i]) {
713 case SVOLM:
714 k = snd_vol;
715 break;
716 case MVOLM:
717 k = mus_vol;
718 break;
719 case GAMMAM:
720 k = gamma << 5;
721 break;
722 default:
723 k = 0;
724 break;
726 R_gl_draw_image(&mbaro, cx - mnu->x + 8 + k, j, 0);
727 break;
731 R_gl_draw_image(&msklh[(gm_tm / 6) & 1], cx - mnu->x - 25, y + mnu->cur * 16 + 20 - 8, 0);
732 } else if (mnu->type == MSG) {
733 Z_gotoxy(cx - strlen(mnu->ttl) * 7 / 2, cy - 10); Z_printsf(mnu->ttl);
734 Z_gotoxy(cx - 24, SCRH / 2); Z_printsf("(Y/N)");
735 } else {
736 ERR_fatal("Unknown menu type %i\n", mnu->type);
741 /* --- View --- */
743 static void R_draw_fld (byte *fld, int minx, int miny, int maxx, int maxy, int fg) {
744 int i, j;
745 assert(minx >= 0 && minx <= FLDW);
746 assert(miny >= 0 && miny <= FLDH);
747 assert(maxx >= 0 && maxx <= FLDW);
748 assert(maxy >= 0 && maxy <= FLDH);
749 for (j = miny; j < maxy; j++) {
750 for (i = minx; i < maxx; i++) {
751 byte id = fld[j * FLDW + i];
752 if (id != 0) {
753 if (walp[id].res < 0) {
754 if (fg) {
755 switch (R_get_special_id(id)) {
756 case 1:
757 glColor4ub(0, 0, 255, 127);
758 break;
759 case 2:
760 glColor4ub(0, 127, 0, 127);
761 break;
762 case 3:
763 glColor4ub(127, 0, 0, 127);
764 break;
765 default:
766 glColor4ub(0, 0, 0, 127);
767 break;
769 glEnable(GL_BLEND);
770 glBlendFunc(GL_DST_COLOR, GL_SRC_COLOR);
771 glDisable(GL_TEXTURE_2D);
772 R_gl_draw_quad(i * CELW, j * CELW, CELW, CELH);
774 } else {
775 R_gl_draw_image(&walp[id], i * CELW, j * CELH, 0);
782 static void R_draw_dots (void) {
783 int i;
784 glDisable(GL_BLEND);
785 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
786 glDisable(GL_TEXTURE_2D);
787 glBegin(GL_POINTS);
788 for (i = 0; i < MAXDOT; i++) {
789 if (dot[i].t != 0) {
790 R_gl_set_color(dot[i].c);
791 glVertex2i(dot[i].o.x, dot[i].o.y + 1);
794 glEnd();
797 static void R_draw_items (void) {
798 int i, s;
799 for (i = 0; i < MAXITEM; ++i) {
800 s = -1;
801 if (it[i].t && it[i].s >= 0) {
802 switch (it[i].t & 0x7FFF) {
803 case I_ARM1:
804 s = it[i].s / 9 + 18;
805 break;
806 case I_ARM2:
807 s = it[i].s / 9 + 20;
808 break;
809 case I_MEGA:
810 s = it[i].s / 2 + 22;
811 break;
812 case I_INVL:
813 s = it[i].s / 2 + 26;
814 break;
815 case I_SUPER:
816 case I_RTORCH:
817 case I_GTORCH:
818 case I_BTORCH:
819 s = it[i].s / 2 + (it[i].t - I_SUPER) * 4 + 35;
820 break;
821 case I_GOR1: case I_FCAN:
822 s = it[i].s / 2 + (it[i].t - I_GOR1) * 3 + 51;
823 break;
824 case I_AQUA:
825 s = 30;
826 break;
827 case I_SUIT:
828 s = 34;
829 break;
830 case I_KEYR:
831 case I_KEYG:
832 case I_KEYB:
833 s = (it[i].t & 0x7FFF) - I_KEYR + 31;
834 break;
835 case I_GUN2:
836 s = 57;
837 break;
838 default:
839 s = (it[i].t & 0x7FFF) - 1;
842 if (s >= 0) {
843 R_gl_draw_image(&item_spr[s], it[i].o.x, it[i].o.y, item_sprd[s]);
848 static int standspr (player_t *p) {
849 if (p->f & PLF_UP) {
850 return 'X';
851 } else if (p->f & PLF_DOWN) {
852 return 'Z';
853 } else {
854 return 'E';
858 static int wpnspr (player_t *p) {
859 if (p->f & PLF_UP) {
860 return 'C';
861 } else if(p->f & PLF_DOWN) {
862 return 'E';
863 } else {
864 return 'A';
868 static void R_draw_player (player_t *p) {
869 enum {STAND, GO, DIE, SLOP, DEAD, MESS, OUT, FALL}; // copypasted from player.c!
870 static const int wytab[] = {-1, -2, -1, 0};
871 int s = 'A';
872 int w = 0;
873 int wx = 0;
874 int wy = 0;
875 switch (p->st) {
876 case STAND:
877 if (p->f & PLF_FIRE) {
878 s = standspr(p) + 1;
879 w = wpnspr(p) + 1;
880 } else if (p->pain) {
881 s = 'G';
882 w = 'A';
883 wx = p->d ? 2 : -2;
884 wy = 1;
885 } else {
886 s = standspr(p);
887 w = wpnspr(p);
889 break;
890 case DEAD:
891 s = 'N';
892 break;
893 case MESS:
894 s = 'W';
895 break;
896 case GO:
897 if (p->pain) {
898 s = 'G';
899 w = 'A';
900 wx = p->d ? 2 : -2;
901 wy = 1;
902 } else {
903 s = plr_goanim[p->s / 8];
904 w = (p->f & PLF_FIRE) ? 'B' : 'A';
905 wx = p->d ? 2 : -2;
906 wy = 1 + wytab[s - 'A'];
908 break;
909 case DIE:
910 s = plr_dieanim[p->s];
911 break;
912 case SLOP:
913 s = plr_slopanim[p->s];
914 break;
915 case OUT:
916 s = 0;
917 break;
919 if (p->wpn == 0) {
920 w = 0;
922 if (w) {
923 R_gl_draw_image(&plr_wpn[(int)p->wpn][w -'A'], p->o.x + wx, p->o.y + wy, p->d);
925 if (s) {
926 R_gl_draw_image(&plr_spr[(s - 'A') * 2 + p->d], p->o.x, p->o.y, plr_sprd[(s - 'A') * 2 + p->d]);
927 R_gl_set_color(p->color + PLAYER_COLOR_OFFSET);
928 R_gl_draw_image_color(&plr_msk[(s - 'A') * 2 + p->d], p->o.x, p->o.y, plr_sprd[(s - 'A') * 2 + p->d]);
932 static void R_draw_monsters (void) {
933 enum {SLEEP, GO, RUN, CLIMB, DIE, DEAD, ATTACK, SHOOT, PAIN, WAIT, REVIVE, RUNOUT}; // copypasted from monster.c!
934 int i;
935 for (i = 0; i < MAXMN; i++) {
936 if (mn[i].t != MN_NONE) {
937 int x = mn[i].o.x;
938 int y = mn[i].o.y;
939 if (mn[i].t < MN__LAST) {
940 if ((mn[i].t != MN_SOUL && mn[i].t != MN_PAIN) || mn[i].st != DEAD) {
941 int ap = mn[i].ap[mn[i].ac];
942 int d = (ap - 'A') * 2 + mn[i].d;
943 int dir = mn_sprd[mn[i].t - 1][d];
944 if (mn[i].t == MN_MAN && (ap == 'E' || ap == 'F')) {
945 R_gl_draw_image(&mn_sgun[ap - 'E'], x, y, mn[i].d);
947 R_gl_draw_image(&mn_spr[mn[i].t - 1][d], x, y, dir);
948 if (mn[i].t == MN_MAN) {
949 R_gl_set_color(MANCOLOR + PLAYER_COLOR_OFFSET);
950 R_gl_draw_image_color(&mn_man_msk[d], x, y, dir);
953 if (mn[i].t == MN_VILE && mn[i].st == SHOOT) {
954 R_gl_draw_image(&mn_fspr[mn[i].ac / 3], mn[i].tx, mn[i].ty, 0);
956 } else if (mn[i].t == MN_PL_DEAD || mn[i].t == MN_PL_MESS) {
957 int type = mn[i].t - MN_PL_DEAD;
958 R_gl_draw_image(&pl_spr[type], x, y, 0);
959 R_gl_set_color(mn[i].d);
960 R_gl_draw_image_color(&pl_msk[type], x, y, 0);
966 static void R_draw_weapons (void) {
967 enum {NONE, ROCKET, PLASMA, APLASMA, BALL1, BALL2, BALL7, BFGBALL, BFGHIT, MANF, REVF, FIRE}; // copypasted from weapons.c!
968 int i, s, d, x, y;
969 for (i = 0; i < MAXWPN; ++i) {
970 s = -1;
971 d = 0;
972 switch (wp[i].t) {
973 case REVF:
974 case ROCKET:
975 d = wp[i].s;
976 if (d < 2) {
977 d = wp[i].o.xv > 0 ? 1 : 0;
978 x = abs(wp[i].o.xv);
979 y = wp[i].o.yv;
980 s = 0;
981 if (y < 0) {
982 if (-y >= x) {
983 s = 30;
985 } else if (y > 0) {
986 if (y >= x / 2) {
987 s = 31;
990 } else {
991 s = (d - 2) / 2 + 1;
992 d = 0;
994 break;
995 case MANF:
996 s=wp[i].s;
997 if (s >= 2) {
998 s /= 2;
999 break;
1001 case PLASMA:
1002 case APLASMA:
1003 case BALL1:
1004 case BALL7:
1005 case BALL2:
1006 s = wp[i].s;
1007 if (s >= 2) {
1008 s = s / 2 + 1;
1010 switch (wp[i].t) {
1011 case PLASMA:
1012 s += 4;
1013 break;
1014 case APLASMA:
1015 s += 11;
1016 break;
1017 case BALL1:
1018 s += 32;
1019 break;
1020 case BALL2:
1021 s += 42;
1022 break;
1023 case BALL7:
1024 s += 37;
1025 d = wp[i].o.xv >= 0 ? 1 : 0;
1026 break;
1027 case MANF:
1028 s += 47;
1029 d= wp[i].o.xv>=0 ? 1 : 0;
1030 break;
1032 break;
1033 case BFGBALL:
1034 s = wp[i].s;
1035 if (s >= 2) {
1036 s = s / 2 + 1;
1038 s += 18;
1039 break;
1040 case BFGHIT:
1041 s = wp[i].s / 2 + 26;
1042 break;
1044 if (s >= 0) {
1045 R_gl_draw_image(&wp_spr[s * 2 + d], wp[i].o.x, wp[i].o.y, wp_sprd[s * 2 + d]);
1050 static void R_draw_smoke (void) {
1051 int i, s;
1052 for (i = 0; i < MAXSMOK; ++i) {
1053 if (sm[i].t) {
1054 switch (sm[i].s) {
1055 case 0:
1056 s = sm[i].t;
1057 if (s >= (SMSN - 1) * 3) {
1058 s = 0;
1059 } else {
1060 s = SMSN - 1 - s / 3;
1062 R_gl_draw_image(&smk_spr[s], sm[i].x >> 8, (sm[i].y >> 8) + 1, 0);
1063 break;
1064 case 1:
1065 s = sm[i].t;
1066 if (s >= FLSN - 1) {
1067 s = 0;
1068 } else {
1069 s = FLSN - 1 - s;
1071 R_gl_draw_image(&smk_fspr[s], sm[i].x >> 8, (sm[i].y >> 8) + 1, 0);
1072 break;
1078 static void R_draw_effects (void) {
1079 enum {NONE, TFOG, IFOG, BUBL}; // copypasted from fx.c
1080 int i, s;
1081 for (i = 0; i < MAXFX; ++i) {
1082 switch (fx[i].t) {
1083 case TFOG:
1084 s = fx[i].s / 2;
1085 R_gl_draw_image(&fx_spr[s], fx[i].x, fx[i].y, fx_sprd[s]);
1086 break;
1087 case IFOG:
1088 s = fx[i].s / 2 + 10;
1089 R_gl_draw_image(&fx_spr[s], fx[i].x, fx[i].y, fx_sprd[s]);
1090 break;
1091 case BUBL:
1092 glDisable(GL_BLEND);
1093 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
1094 glDisable(GL_TEXTURE_2D);
1095 glBegin(GL_POINTS);
1096 R_gl_set_color(0xC0 + fx[i].s);
1097 glVertex2i(fx[i].x >> 8, (fx[i].y >> 8) + 1);
1098 glEnd();
1099 break;
1104 static int get_pu_st (int t) {
1105 if (t >= PL_FLASH) {
1106 return 1;
1107 } else if((t / 9) & 1) {
1108 return 0;
1109 } else {
1110 return 1;
1114 static void R_draw_view (int x, int y, int w, int h, int camx, int camy) {
1115 glPushMatrix();
1116 R_gl_setclip(x, y, w, h);
1117 glTranslatef(x, y, 0);
1118 if (w_horiz && horiz.n != NULL) {
1119 R_gl_draw_image_ext(&horiz, 0, 0, w, h);
1120 if (sky_type == 2 && lt_time < 0) {
1121 image *tanderbolt = &ltn[lt_type][lt_time < -5 ? 0 : 1];
1122 if (!lt_side) {
1123 R_gl_draw_image(tanderbolt, 0, lt_ypos, 0);
1124 } else {
1125 R_gl_draw_image(tanderbolt, w - 1, lt_ypos, 1);
1128 } else {
1129 glDisable(GL_BLEND);
1130 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
1131 glDisable(GL_TEXTURE_2D);
1132 R_gl_set_color(DEFAULT_SKY_COLOR);
1133 R_gl_draw_quad(0, 0, w, h);
1135 int maxx = min((camx + w) / CELW + 1, FLDW);
1136 int maxy = min((camy + h) / CELH + 1, FLDH);
1137 int minx = max((camx - max_wall_width) / CELW, 0);
1138 int miny = max((camy - max_wall_height) / CELH, 0);
1139 glTranslatef(-camx, -camy, 0);
1140 R_draw_fld((byte*)fldb, minx, miny, maxx, maxy, 0);
1141 R_draw_dots();
1142 R_draw_items();
1143 R_draw_player(&pl1);
1144 if (_2pl) {
1145 R_draw_player(&pl2);
1147 R_draw_monsters();
1148 R_draw_weapons();
1149 R_draw_smoke();
1150 R_draw_effects();
1151 R_draw_fld((byte*)fldf, minx, miny, maxx, maxy, 1);
1152 glTranslatef(camx, camy, 0);
1153 if (sky_type == 2 && (lt_time == -4 || lt_time == -2)) {
1154 glColor4ub(255, 255, 255, 255);
1155 glEnable(GL_BLEND);
1156 glBlendFunc(GL_DST_COLOR, GL_SRC_COLOR);
1157 glDisable(GL_TEXTURE_2D);
1158 R_gl_draw_quad(0, 0, w, h);
1160 glPopMatrix();
1163 static void R_draw_player_view (player_t *p, int x, int y, int w, int h) {
1164 p->looky = min(max(p->looky, -SCRH / 4), SCRH / 4); // TODO remove writeback
1165 int st = stone.w;
1166 int cw = w - st;
1167 int cx = min(max(p->o.x, cw / 2), FLDW * CELW - cw / 2);
1168 int cy = min(max(p->o.y - 12 + p->looky, h / 2), FLDH * CELH - h / 2);
1169 int camx = max(cx - cw / 2, 0);
1170 int camy = max(cy - h / 2, 0);
1171 glPushMatrix();
1172 R_draw_view(x, y + 1, cw, h - 2, camx, camy);
1173 glTranslatef(x, y, 0);
1174 if (p->invl) {
1175 if (get_pu_st(p->invl)) {
1176 glEnable(GL_BLEND);
1177 glBlendFunc(GL_ONE_MINUS_DST_COLOR, GL_ZERO);
1178 glDisable(GL_TEXTURE_2D);
1179 glColor4ub(191, 191, 191, 255);
1180 R_gl_draw_quad(0, 0, cw, h);
1182 } else {
1183 if (p->suit && get_pu_st(p->suit)) {
1184 glEnable(GL_BLEND);
1185 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
1186 glDisable(GL_TEXTURE_2D);
1187 glColor4ub(0, 255, 0, 192);
1188 R_gl_draw_quad(0, 0, cw, h);
1190 int f = min(max(p->pain * 3, 0), 255);
1191 if (f > 0) {
1192 glEnable(GL_BLEND);
1193 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
1194 glDisable(GL_TEXTURE_2D);
1195 glColor4ub(255, 0, 0, f);
1196 R_gl_draw_quad(0, 0, cw, h);
1199 R_gl_setclip(x, y, w, h);
1200 glTranslatef(-x + cw, 0, 0);
1201 R_gl_draw_image(&stone, 0, 0, 0);
1202 int i = stone.h;
1203 while (i < h) {
1204 R_gl_draw_image(&stone2, 0, i, 0);
1205 i += stone2.h;
1207 if (p->drawst & PL_DRAWAIR) {
1208 if (p->air < PL_AIR) {
1209 int a = min(max(p->air, 0), MAXAIR) * 100 / MAXAIR;
1210 glDisable(GL_BLEND);
1211 glBlendFunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA);
1212 glDisable(GL_TEXTURE_2D);
1213 R_gl_set_color(0xC8);
1214 R_gl_draw_quad(10, 49, a, 2);
1217 if (p->drawst & PL_DRAWLIFE) {
1218 Z_gotoxy(10, 7);
1219 Z_printhf("%3d%%", p->life);
1221 if (p->drawst & PL_DRAWARMOR) {
1222 Z_gotoxy(10, 7 + 19);
1223 Z_printhf("%3d%%", p->armor);
1225 if (p->drawst & PL_DRAWWPN) {
1226 switch(p->wpn) {
1227 case 2:
1228 case 5:
1229 i = p->ammo;
1230 break;
1231 case 3:
1232 case 4:
1233 case 9:
1234 i = p->shel;
1235 break;
1236 case 6:
1237 i = p->rock;
1238 break;
1239 case 7:
1240 case 8:
1241 i = p->cell;
1242 break;
1243 case 10:
1244 i = p->fuel;
1245 break;
1246 default:
1247 i = -1;
1248 break;
1250 // weapon
1251 if (p->wpn >= 0) {
1252 R_gl_draw_image(&sth[12 + p->wpn], st - 88, 58 + 19, 0);
1254 // ammo
1255 if (p->wpn >= 2) {
1256 Z_gotoxy(st - 10 - 5 * 14, 58 + 2);
1257 Z_printhf("%5d", i);
1260 if (p->drawst & PL_DRAWFRAG && g_dm) {
1261 Z_gotoxy(st - 5 - 5 * 14, 77 + 5);
1262 Z_printhf("%5d", p->frag);
1264 if (p->drawst & PL_DRAWKEYS) {
1265 int x, k, n;
1266 for (k = p->keys >> 4, n = 0, x = st - 75; n < 3; n++, k >>= 1, x += 9) {
1267 if (k & 1) {
1268 R_gl_draw_image(&keys[n], x, 91, 0);
1272 if (p->drawst & PL_DRAWLIVES && !_2pl) {
1273 Z_gotoxy(st - 35, 17);
1274 Z_printhf("%d", p->lives);
1276 glPopMatrix();
1279 /* --- Game --- */
1281 static void pl_info (player_t *p, int x, int y) {
1282 dword t = p->kills * 10920 / g_time;
1283 Z_gotoxy(x + 25, y); Z_printbf("KILLS");
1284 Z_gotoxy(x + 25, y + 15); Z_printbf("KPM");
1285 Z_gotoxy(x + 25, y + 30); Z_printbf("SECRETS %u / %u", p->secrets, sw_secrets);
1286 Z_gotoxy(x + 255, y); Z_printbf("%u", p->kills);
1287 Z_gotoxy(x + 255, y + 15); Z_printbf("%u.%u", t / 10, t % 10);
1290 static void R_draw_intermission (void) {
1291 int cx = SCRW / 2;
1292 word hr, mn, sc, h;
1293 Z_gotoxy(cx - 14*12/2, 20);
1294 Z_printbf("LEVEL COMPLETE");
1295 Z_calc_time(g_time, &hr, &mn, &sc);
1296 Z_gotoxy(cx - 12*12/2, 40);
1297 Z_printbf("TIME %u:%02u:%02u", hr, mn, sc);
1298 h = 40 + SCRH / 10;
1299 if (_2pl) {
1300 Z_gotoxy(cx - 10*12/2, h);
1301 Z_printbf("PLAYER ONE");
1302 h += 20;
1304 pl_info(&pl1, cx - 160, h);
1305 if (_2pl) {
1306 h += 30 + SCRH / 10;
1307 Z_gotoxy(cx - 10*12/2, h);
1308 Z_printbf("PLAYER TWO");
1309 h += 20;
1310 pl_info(&pl2, cx - 160, h);
1314 static void W_act (void) {
1315 int i, a;
1316 if (g_time % 3 == 0) {
1317 for (i = 1; i < max_textures; i++) {
1318 a = walani[i];
1319 if (a != 0) {
1320 anic[a]++;
1321 if (anip[a][anic[a]].res == -1) {
1322 anic[a] = 0;
1324 walp[i] = anip[a][anic[a]];
1330 void R_draw (void) {
1331 W_act();
1332 glClearColor(0, 0, 0, 1);
1333 glClear(GL_COLOR_BUFFER_BIT);
1334 glEnable(GL_SCISSOR_TEST);
1335 R_gl_setmatrix();
1336 switch (g_st) {
1337 case GS_ENDANIM:
1338 case GS_END2ANIM:
1339 case GS_DARKEN:
1340 case GS_BVIDEO:
1341 case GS_EVIDEO:
1342 case GS_END3ANIM:
1343 break;
1344 case GS_TITLE:
1345 R_gl_draw_image_ext(&scrnh[0], 0, 0, SCRW, SCRH);
1346 break;
1347 case GS_INTER:
1348 R_gl_draw_image_ext(&scrnh[1], 0, 0, SCRW, SCRH);
1349 R_draw_intermission();
1350 break;
1351 case GS_ENDSCR:
1352 R_gl_draw_image_ext(&scrnh[2], 0, 0, SCRW, SCRH);
1353 break;
1354 case GS_GAME:
1355 if (_2pl) {
1356 R_draw_player_view(&pl1, 0, 0, SCRW, SCRH / 2);
1357 R_draw_player_view(&pl2, 0, SCRH / 2, SCRW, SCRH / 2);
1358 } else {
1359 R_draw_player_view(&pl1, 0, 0, SCRW, SCRH);
1361 R_gl_setclip(0, 0, SCRW, SCRH);
1362 break;
1364 GM_draw();
1365 SDL_GL_SwapBuffers();
1368 void R_alloc (void) {
1369 char s[10];
1370 int i, j, n;
1371 logo("R_alloc: load graphics\n");
1372 /* Game */
1373 scrnh[0] = R_gl_loadimage("TITLEPIC");
1374 assert(scrnh[0].n);
1375 scrnh[1] = R_gl_loadimage("INTERPIC");
1376 scrnh[2] = R_gl_loadimage("ENDPIC");
1377 for (i = 0; i < 2; i++) {
1378 sprintf(s, "LTN%c", '1' + i);
1379 for (j = 0; j < 2; j++) {
1380 ltn[i][j] = Z_getspr(s, j, 0, NULL);
1383 /* Smoke */
1384 for (i = 0; i < SMSN; i++) {
1385 smk_spr[i] = R_gl_get_special_spr("SMOK", i, 0, &R_extract_smoke_spr);
1387 for (i = 0; i < FLSN; i++) {
1388 smk_fspr[i] = R_gl_get_special_spr("SMOK", i, 0, &R_extract_flame_spr);
1390 /* Effects */
1391 for (i = 0; i < 10; i++) {
1392 fx_spr[i] = Z_getspr("TFOG", i, 0, fx_sprd + i);
1394 for (; i < 15; i++) {
1395 fx_spr[i] = Z_getspr("IFOG", i - 10, 0, fx_sprd + i);
1397 /* Weapons */
1398 for (i = 0; i < 4; i++) {
1399 wp_spr[i * 2] = Z_getspr("MISL", i, 1, wp_sprd + i * 2);
1400 wp_spr[i * 2 + 1] = Z_getspr("MISL", i, 2, wp_sprd + i * 2 + 1);
1402 for (; i < 6; i++) {
1403 wp_spr[i * 2] = Z_getspr("PLSS", i - 4, 1, wp_sprd + i * 2);
1404 wp_spr[i * 2 + 1] = Z_getspr("PLSS", i - 4, 2, wp_sprd + i * 2 + 1);
1406 for (; i < 11; i++) {
1407 wp_spr[i * 2] = Z_getspr("PLSE", i - 6, 1, wp_sprd + i * 2);
1408 wp_spr[i * 2 + 1] = Z_getspr("PLSE", i - 6, 2, wp_sprd + i * 2 + 1);
1410 for (; i < 13; i++) {
1411 wp_spr[i * 2] = Z_getspr("APLS", i - 11, 1, wp_sprd + i * 2);
1412 wp_spr[i * 2 + 1] = Z_getspr("APLS", i - 11, 2, wp_sprd + i * 2 + 1);
1414 for (; i < 18; i++) {
1415 wp_spr[i * 2] = Z_getspr("APBX", i - 13, 1, wp_sprd + i * 2);
1416 wp_spr[i * 2 + 1] = Z_getspr("APBX", i - 13, 2, wp_sprd + i * 2 + 1);
1418 for(; i < 20; i++) {
1419 wp_spr[i * 2] = Z_getspr("BFS1", i - 18, 1, wp_sprd + i * 2);
1420 wp_spr[i * 2 + 1] = Z_getspr("BFS1", i - 18, 2, wp_sprd + i * 2 + 1);
1422 for (; i < 26; i++) {
1423 wp_spr[i * 2] = Z_getspr("BFE1", i - 20, 1, wp_sprd + i * 2);
1424 wp_spr[i * 2 + 1] = Z_getspr("BFE1", i - 20, 2, wp_sprd + i * 2 + 1);
1426 for (; i < 30; i++) {
1427 wp_spr[i * 2] = Z_getspr("BFE2", i - 26, 1, wp_sprd + i * 2);
1428 wp_spr[i * 2 + 1] = Z_getspr("BFE2", i - 26, 2, wp_sprd + i * 2 + 1);
1430 for (; i < 32; i++) {
1431 wp_spr[i * 2] = Z_getspr("MISL", i - 30 + 4, 1, wp_sprd + i * 2);
1432 wp_spr[i * 2 + 1] = Z_getspr("MISL", i - 30 + 4, 2, wp_sprd + i * 2 + 1);
1434 for (; i < 37; i++) {
1435 wp_spr[i * 2] = Z_getspr("BAL1", i - 32, 1, wp_sprd + i * 2);
1436 wp_spr[i * 2 + 1] = Z_getspr("BAL1", i - 32, 2, wp_sprd + i * 2 + 1);
1438 for (; i < 42; i++) {
1439 wp_spr[i * 2] = Z_getspr("BAL7", i - 37, 1, wp_sprd + i * 2);
1440 wp_spr[i * 2 + 1] = Z_getspr("BAL7", i - 37, 2, wp_sprd + i * 2 + 1);
1442 for (; i < 47; i++) {
1443 wp_spr[i * 2] = Z_getspr("BAL2", i - 42, 1, wp_sprd + i * 2);
1444 wp_spr[i * 2 + 1] = Z_getspr("BAL2", i - 42, 2, wp_sprd + i * 2 + 1);
1446 for (; i < 49; i++) {
1447 wp_spr[i * 2] = Z_getspr("MANF", i - 47, 1, wp_sprd + i * 2);
1448 wp_spr[i * 2 + 1] = Z_getspr("MANF", i - 47, 2, wp_sprd + i * 2 + 1);
1450 /* Items */
1451 static const char snm[18][4] = {
1452 "CLIP", "SHEL", "ROCK", "CELL", "AMMO", "SBOX", "BROK", "CELP",
1453 "STIM", "MEDI", "BPAK",
1454 "CSAW", "SHOT", "SGN2", "MGUN", "LAUN", "PLAS", "BFUG"
1455 };
1456 static const char n4[4][4] = {
1457 "SOUL", "SMRT", "SMGT", "SMBT"
1458 };
1459 static const char n3[2][4] = {
1460 "GOR1", "FCAN"
1461 };
1462 for (i = 0; i < 18; i++) {
1463 item_spr[i] = Z_getspr(snm[i], 0, 0, item_sprd + i);
1465 for (; i < 20; i++) {
1466 item_spr[i] = Z_getspr("ARM1", i - 18, 0, item_sprd + i);
1467 item_spr[i + 2] = Z_getspr("ARM2", i - 18, 0, item_sprd + i);
1469 i+=2;
1470 for (; i < 26; i++) {
1471 item_spr[i] = Z_getspr("MEGA", i - 22, 0, item_sprd + i);
1473 for (; i < 30; i++) {
1474 item_spr[i] = Z_getspr("PINV", i - 26, 0, item_sprd + i);
1476 item_spr[30] = Z_getspr("AQUA", 0, 0, item_sprd + 30);
1477 item_spr[31] = Z_getspr("KEYR", 0, 0, item_sprd + 31);
1478 item_spr[32] = Z_getspr("KEYG", 0, 0, item_sprd + 32);
1479 item_spr[33] = Z_getspr("KEYB", 0, 0, item_sprd + 33);
1480 item_spr[34] = Z_getspr("SUIT", 0, 0, item_sprd + 34);
1481 for (n = 35, j = 0; j < 4; j++) {
1482 for (i = 0; i < 4; i++, n++) {
1483 item_spr[n] = Z_getspr(n4[j], i, 0, item_sprd + n);
1486 for (j = 0; j < 2; j++) {
1487 for (i = 0; i < 3; i++, n++) {
1488 item_spr[n] = Z_getspr(n3[j], i, 0, item_sprd + n);
1491 item_spr[57] = Z_getspr("GUN2", 0, 0, item_sprd + 57);
1492 /* Player */
1493 for (i = 0; i < 27; i++) {
1494 plr_spr[i * 2] = Z_getspr("PLAY", i, 1, plr_sprd + i * 2);
1495 plr_msk[i * 2] = R_gl_get_special_spr("PLAY", i, 1, &R_extract_mask_spr);
1496 plr_spr[i * 2 + 1] = Z_getspr("PLAY", i, 2, plr_sprd + i * 2 + 1);
1497 plr_msk[i * 2 + 1] = R_gl_get_special_spr("PLAY", i, 2, &R_extract_mask_spr);
1499 strncpy(s, "PWPx", 4);
1500 for (i = 1; i < 11; i++) {
1501 s[3] = (i < 10 ? '0' : 'A' - 10) + i;
1502 for (j = 0; j < 6; j++) {
1503 plr_wpn[i][j] = Z_getspr(s, j, 1, NULL);
1506 /* Monsters */
1507 static const char msn[MN_TN][4] = {
1508 "SARG", "TROO", "POSS", "SPOS", "CYBR", "CPOS", "BOSS", "BOS2", "HEAD", "SKUL",
1509 "PAIN", "SPID", "BSPI", "FATT", "SKEL", "VILE", "FISH", "BAR1", "ROBO", "PLAY"
1510 };
1511 static const int mms[MN_TN] = {
1512 14*2, 21*2, 21*2, 21*2, 16*2, 20*2, 15*2, 15*2, 12*2, 11*2,
1513 13*2, 19*2, 16*2, 20*2, 17*2, 29*2, 6*2, 2*2, 17*2, 23*2
1514 };
1515 mn_sgun[0] = Z_getspr("PWP4", 0, 1, NULL);
1516 mn_sgun[1] = Z_getspr("PWP4", 1, 1, NULL);
1517 for (j = 0; j < MN_TN; j++) {
1518 for (i = 0; i < mms[j]; i++) {
1519 mn_spr[j][i] = Z_getspr(msn[j], i / 2, (i & 1) + 1, &mn_sprd[j][i]);
1520 if (j == MN_MAN - 1) {
1521 mn_man_msk[i] = R_gl_get_special_spr(msn[j], i / 2, (i & 1) + 1, &R_extract_mask_spr);
1524 if (j == MN_BARREL - 1) {
1525 for (i = 4; i < 14; i++) {
1526 mn_spr[j][i] = Z_getspr("BEXP", i / 2 - 2, (i & 1) + 1, &mn_sprd[j][i]);
1530 for (i = 0; i < 8; i++) {
1531 mn_fspr[i] = Z_getspr("FIRE", i, 0, NULL);
1533 pl_spr[0] = Z_getspr("PLAY", 'N' - 'A', 0, NULL);
1534 pl_msk[0] = R_gl_get_special_spr("PLAY", 'N' - 'A', 0, &R_extract_mask_spr);
1535 pl_spr[1] = Z_getspr("PLAY", 'W' - 'A', 0, NULL);
1536 pl_msk[1] = R_gl_get_special_spr("PLAY", 'W' - 'A', 0, &R_extract_mask_spr);
1537 /* Misc */
1538 static const char mnm[22][8]={
1539 "STTNUM0", "STTNUM1", "STTNUM2", "STTNUM3", "STTNUM4",
1540 "STTNUM5", "STTNUM6", "STTNUM7", "STTNUM8", "STTNUM9",
1541 "STTMINUS", "STTPRCNT",
1542 "FISTA0", "CSAWA0", "PISTA0", "SHOTA0", "SGN2A0", "MGUNA0", "LAUNA0",
1543 "PLASA0", "BFUGA0", "GUN2A0"
1544 };
1545 stone = R_gl_loadimage("STONE");
1546 stone2 = R_gl_loadimage("STONE2");
1547 keys[0] = R_gl_loadimage("KEYRA0");
1548 keys[1] = R_gl_loadimage("KEYGA0");
1549 keys[2] = R_gl_loadimage("KEYBA0");
1550 for (i = 0; i < 22; i++) {
1551 sth[i] = R_gl_loadimage(mnm[i]);
1553 strcpy(s, "STBF_*");
1554 for (i = '!'; i < 160; i++) {
1555 s[5] = i;
1556 bfh[i - '!'] = R_gl_getimage(F_findres(s));
1558 for (i = '!'; i < 160; i++) {
1559 sprintf(s, "STCFN%03d", i);
1560 sfh[i - '!'] = R_gl_getimage(F_findres(s));
1562 strcpy(s, "WINUM*");
1563 for (i = '0'; i <= '9'; i++) {
1564 s[5] = i;
1565 bfh[i - '!'] = R_gl_loadimage(s);
1567 bfh[':' - '!'] = R_gl_loadimage("WICOLON");
1568 // menu
1569 msklh[0] = R_gl_loadimage("M_SKULL1");
1570 msklh[1] = R_gl_loadimage("M_SKULL2");
1571 mbarl = R_gl_loadimage("M_THERML");
1572 mbarm = R_gl_loadimage("M_THERMM");
1573 mbarr = R_gl_loadimage("M_THERMR");
1574 mbaro = R_gl_loadimage("M_THERMO");
1575 mslotl = R_gl_loadimage("M_LSLEFT");
1576 mslotm = R_gl_loadimage("M_LSCNTR");
1577 mslotr = R_gl_loadimage("M_LSRGHT");
1578 // walls
1579 for (i = 1; i < ANIT; i++) {
1580 for (j = 0; anm[i - 1][j]; j++) {
1581 anip[i][j] = R_gl_loadimage(anm[i - 1][j]);
1583 for(; j < 5; j++) {
1584 anip[i][j] = (image) {
1585 .n = NULL,
1586 .w = 8,
1587 .h = 8,
1588 .res = -1,
1589 };
1594 void R_init (void) {
1595 Uint32 flags = SDL_OPENGL;
1596 if (fullscreen) {
1597 flags = flags | SDL_FULLSCREEN;
1599 if (SCRW <= 0 || SCRH <= 0) {
1600 ERR_failinit("Invalid screen size %ix%i\n", SCRW, SCRH);
1602 if (surf == NULL) {
1603 R_init_playpal(); // only onece
1605 surf = SDL_SetVideoMode(SCRW, SCRH, 0, flags);
1606 if (surf == NULL) {
1607 ERR_failinit("Unable to set video mode: %s\n", SDL_GetError());
1609 root = R_cache_new();
1610 assert(root);
1611 R_alloc();
1614 void R_done (void) {
1615 // do nothing
1618 void R_setgamma (int g) {
1619 gamma = g < 0 ? 0 : (g > 4 ? 4 : g);
1622 int R_getgamma (void) {
1623 return gamma;
1626 void R_toggle_fullscreen (void) {
1627 fullscreen = !fullscreen;
1628 if (surf) {
1629 R_init(); // recreate window
1633 void R_get_name (int n, char s[8]) {
1634 assert(n >= 0 && n < 256);
1635 if (walp[n].res == -1) {
1636 memset(s, 0, 8);
1637 } else if (walp[n].res == -2) {
1638 memcpy(s, "_WATER_", 8);
1639 s[7] = '0' + (intptr_t)walp[n].n - 1;
1640 } else if (walani[n] > 0) {
1641 memcpy(s, anm[walani[n] - 1][0], 8);
1642 } else {
1643 F_getresname(s, walp[n].res & 0x7FFF);
1647 static short getani (char n[8]) {
1648 short i = 0;
1649 while (i < ANIT - 1 && strncasecmp(n, anm[i][0], 8) != 0) {
1650 i++;
1652 return i < ANIT - 1 ? i + 1 : 0;
1655 int R_get_special_id (int n) {
1656 assert(n >= 0 && n <= 256);
1657 return walp[n].res == -2 ? (intptr_t)walp[n].n : -1;
1660 void R_begin_load (void) {
1661 int i;
1662 for (i = 0; i < 256; i++) {
1663 if (walp[i].n != NULL && walp[i].res >= 0 && walani[i] == 0) {
1664 R_gl_free_image(&walp[i]);
1666 memset(&walp[i], 0, sizeof(image));
1667 walp[i].res = -1;
1668 walswp[i] = i;
1669 walani[i] = 0;
1671 memset(anic, 0, sizeof(anic));
1672 max_wall_width = 0;
1673 max_wall_height = 0;
1674 max_textures = 1;
1677 void R_load (char s[8], int f) {
1678 assert(max_textures < 256);
1679 if (!s[0]) {
1680 walp[max_textures] = (image) {
1681 .n = NULL,
1682 .x = 0,
1683 .y = 0,
1684 .w = 0,
1685 .h = 0,
1686 .res = -1,
1687 };
1688 } else if (strncasecmp(s, "_WATER_", 7) == 0) {
1689 walp[max_textures] = (image) {
1690 .n = (void*)((intptr_t)s[7] - '0' + 1),
1691 .x = 0,
1692 .y = 0,
1693 .w = 8,
1694 .h = 8,
1695 .res = -2,
1696 };
1697 } else {
1698 walp[max_textures] = R_gl_loadimage(s);
1699 if (f) {
1700 walp[max_textures].res |= 0x8000;
1702 if (s[0] == 'S' && s[1] == 'W' && s[4] == '_') {
1703 walswp[max_textures] = 0;
1705 walani[max_textures] = getani(s);
1707 max_wall_width = max(max_wall_width, walp[max_textures].w);
1708 max_wall_height = max(max_wall_height, walp[max_textures].h);
1709 max_textures++;
1712 void R_end_load (void) {
1713 int i, j, k, g;
1714 char s[8];
1715 j = max_textures;
1716 for (i = 1; i < 256 && j < 256; i++) {
1717 if (walswp[i] == 0) {
1718 R_get_name(i, s);
1719 s[5] ^= 1;
1720 g = F_getresid(s) | (walp[i].res & 0x8000);
1721 k = 1;
1722 while (k < 256 && walp[k].res != g) {
1723 k += 1;
1725 if (k >= 256) {
1726 k = j;
1727 j += 1;
1728 walp[k] = R_gl_getimage(g);
1729 walf[k] = g & 0x8000 ? 1 : 0;
1731 walswp[i] = k;
1732 walswp[k] = i;
1737 void R_loadsky (int sky) {
1738 char s[6];
1739 strcpy(s, "RSKYx");
1740 s[4] = '0' + sky;
1741 R_gl_free_image(&horiz);
1742 horiz = R_gl_loadimage(s);