diff options
Diffstat (limited to 'otherlibs')
-rw-r--r-- | otherlibs/graph/color.c | 112 | ||||
-rw-r--r-- | otherlibs/graph/draw.c | 90 | ||||
-rw-r--r-- | otherlibs/graph/dump_img.c | 10 | ||||
-rw-r--r-- | otherlibs/graph/events.c | 120 | ||||
-rw-r--r-- | otherlibs/graph/fill.c | 46 | ||||
-rw-r--r-- | otherlibs/graph/graphics.ml | 72 | ||||
-rw-r--r-- | otherlibs/graph/graphics.mli | 60 | ||||
-rw-r--r-- | otherlibs/graph/graphicsX11.ml | 6 | ||||
-rw-r--r-- | otherlibs/graph/image.c | 64 | ||||
-rw-r--r-- | otherlibs/graph/image.h | 2 | ||||
-rw-r--r-- | otherlibs/graph/libgraph.h | 58 | ||||
-rw-r--r-- | otherlibs/graph/make_img.c | 38 | ||||
-rw-r--r-- | otherlibs/graph/open.c | 264 | ||||
-rw-r--r-- | otherlibs/graph/point_col.c | 8 | ||||
-rw-r--r-- | otherlibs/graph/sound.c | 12 | ||||
-rw-r--r-- | otherlibs/graph/subwindow.c | 22 | ||||
-rw-r--r-- | otherlibs/graph/text.c | 66 |
17 files changed, 526 insertions, 524 deletions
diff --git a/otherlibs/graph/color.c b/otherlibs/graph/color.c index f47fa5814..cf3380a77 100644 --- a/otherlibs/graph/color.c +++ b/otherlibs/graph/color.c @@ -34,18 +34,18 @@ static int num_overflows = 0; /* rgb -> pixel conversion *without* display connection */ -Bool direct_rgb = False; -int red_l, red_r; -int green_l, green_r; -int blue_l, blue_r; -unsigned long red_mask, green_mask, blue_mask; +Bool caml_gr_direct_rgb = False; +int caml_gr_red_l, caml_gr_red_r; +int caml_gr_green_l, caml_gr_green_r; +int caml_gr_blue_l, caml_gr_blue_r; +unsigned long caml_gr_red_mask, caml_gr_green_mask, caml_gr_blue_mask; /* rgb -> pixel table */ -unsigned long red_vals[256]; -unsigned long green_vals[256]; -unsigned long blue_vals[256]; +unsigned long caml_gr_red_vals[256]; +unsigned long caml_gr_green_vals[256]; +unsigned long caml_gr_blue_vals[256]; -void get_shifts( unsigned long mask, int *lsl, int *lsr ) +void caml_gr_get_shifts( unsigned long mask, int *lsl, int *lsr ) { int l = 0; int r = 0; @@ -66,86 +66,86 @@ void get_shifts( unsigned long mask, int *lsl, int *lsr ) *lsr = 16 - (r - l); } -void gr_init_direct_rgb_to_pixel(void) +void caml_gr_init_direct_rgb_to_pixel(void) { Visual *visual; int i; - visual = DefaultVisual(grdisplay,grscreen); + visual = DefaultVisual(caml_gr_display,caml_gr_screen); if ( visual->class == TrueColor || visual->class == DirectColor ){ int lsl, lsr; - red_mask = visual->red_mask; - green_mask = visual->green_mask; - blue_mask = visual->blue_mask; + caml_gr_red_mask = visual->red_mask; + caml_gr_green_mask = visual->green_mask; + caml_gr_blue_mask = visual->blue_mask; #ifdef QUICKCOLORDEBUG fprintf(stderr, "visual %lx %lx %lx\n", - red_mask, - green_mask, - blue_mask); + caml_gr_red_mask, + caml_gr_green_mask, + caml_gr_blue_mask); #endif - get_shifts(red_mask, &red_l, &red_r); + caml_gr_get_shifts(caml_gr_red_mask, &caml_gr_red_l, &caml_gr_red_r); #ifdef QUICKCOLORDEBUG - fprintf(stderr, "red %d %d\n", red_l, red_r); + fprintf(stderr, "red %d %d\n", caml_gr_red_l, caml_gr_red_r); #endif for(i=0; i<256; i++){ - red_vals[i] = (((i << 8) + i) >> red_r) << red_l; + caml_gr_red_vals[i] = (((i << 8) + i) >> caml_gr_red_r) << caml_gr_red_l; } - get_shifts(green_mask, &green_l, &green_r); + caml_gr_get_shifts(caml_gr_green_mask, &caml_gr_green_l, &caml_gr_green_r); #ifdef QUICKCOLORDEBUG - fprintf(stderr, "green %d %d\n", green_l, green_r); + fprintf(stderr, "green %d %d\n", caml_gr_green_l, caml_gr_green_r); #endif for(i=0; i<256; i++){ - green_vals[i] = (((i << 8) + i) >> green_r) << green_l; + caml_gr_green_vals[i] = (((i << 8) + i) >> caml_gr_green_r) << caml_gr_green_l; } - get_shifts(blue_mask, &blue_l, &blue_r); + caml_gr_get_shifts(caml_gr_blue_mask, &caml_gr_blue_l, &caml_gr_blue_r); #ifdef QUICKCOLORDEBUG - fprintf(stderr, "blue %d %d\n", blue_l, blue_r); + fprintf(stderr, "blue %d %d\n", caml_gr_blue_l, caml_gr_blue_r); #endif for(i=0; i<256; i++){ - blue_vals[i] = (((i << 8) + i) >> blue_r) << blue_l; + caml_gr_blue_vals[i] = (((i << 8) + i) >> caml_gr_blue_r) << caml_gr_blue_l; } - if( red_l < 0 || red_r < 0 || - green_l < 0 || green_r < 0 || - blue_l < 0 || blue_r < 0 ){ + if( caml_gr_red_l < 0 || caml_gr_red_r < 0 || + caml_gr_green_l < 0 || caml_gr_green_r < 0 || + caml_gr_blue_l < 0 || caml_gr_blue_r < 0 ){ #ifdef QUICKCOLORDEBUG fprintf(stderr, "Damn, boost failed\n"); #endif - direct_rgb = False; + caml_gr_direct_rgb = False; } else { #ifdef QUICKCOLORDEBUG fprintf(stderr, "Boost ok\n"); #endif - direct_rgb = True; + caml_gr_direct_rgb = True; } } else { /* we cannot use direct_rgb_to_pixel */ #ifdef QUICKCOLORDEBUG fprintf(stderr, "No boost!\n"); #endif - direct_rgb = False; + caml_gr_direct_rgb = False; } } -void gr_init_color_cache(void) +void caml_gr_init_color_cache(void) { int i; for (i = 0; i < Color_cache_size; i++) color_cache[i].rgb = Empty; i = Hash_rgb(0, 0, 0); color_cache[i].rgb = 0; - color_cache[i].pixel = grblack; + color_cache[i].pixel = caml_gr_black; i = Hash_rgb(0xFF, 0xFF, 0xFF); color_cache[i].rgb = 0xFFFFFF; - color_cache[i].pixel = grwhite; + color_cache[i].pixel = caml_gr_white; } -unsigned long gr_pixel_rgb(int rgb) +unsigned long caml_gr_pixel_rgb(int rgb) { unsigned int r, g, b; int h, i; @@ -156,8 +156,8 @@ unsigned long gr_pixel_rgb(int rgb) g = (rgb >> 8) & 0xFF; b = rgb & 0xFF; - if (direct_rgb){ - return red_vals[r] | green_vals[g] | blue_vals[b]; + if (caml_gr_direct_rgb){ + return caml_gr_red_vals[r] | caml_gr_green_vals[g] | caml_gr_blue_vals[b]; } h = Hash_rgb(r, g, b); @@ -179,28 +179,28 @@ unsigned long gr_pixel_rgb(int rgb) color.red = r * 0x101; color.green = g * 0x101; color.blue = b * 0x101; - XAllocColor(grdisplay, grcolormap, &color); + XAllocColor(caml_gr_display, caml_gr_colormap, &color); color_cache[i].rgb = rgb; color_cache[i].pixel = color.pixel; return color.pixel; } -int gr_rgb_pixel(long unsigned int pixel) +int caml_gr_rgb_pixel(long unsigned int pixel) { register int r,g,b; XColor color; int i; - if (direct_rgb) { - r = (((pixel & red_mask) >> red_l) << 8) >> (16 - red_r); - g = (((pixel & green_mask) >> green_l) << 8) >> (16 - green_r); - b = (((pixel & blue_mask) >> blue_l) << 8) >> (16 - blue_r); + if (caml_gr_direct_rgb) { + r = (((pixel & caml_gr_red_mask) >> caml_gr_red_l) << 8) >> (16 - caml_gr_red_r); + g = (((pixel & caml_gr_green_mask) >> caml_gr_green_l) << 8) >> (16 - caml_gr_green_r); + b = (((pixel & caml_gr_blue_mask) >> caml_gr_blue_l) << 8) >> (16 - caml_gr_blue_r); return (r << 16) + (g << 8) + b; } - if (pixel == grblack) return 0; - if (pixel == grwhite) return 0xFFFFFF; + if (pixel == caml_gr_black) return 0; + if (pixel == caml_gr_white) return 0xFFFFFF; /* Probably faster to do a linear search than to query the X server. */ for (i = 0; i < Color_cache_size; i++) { @@ -208,23 +208,23 @@ int gr_rgb_pixel(long unsigned int pixel) return color_cache[i].rgb; } color.pixel = pixel; - XQueryColor(grdisplay, grcolormap, &color); + XQueryColor(caml_gr_display, caml_gr_colormap, &color); return ((color.red >> 8) << 16) + ((color.green >> 8) << 8) + (color.blue >> 8); } -value gr_set_color(value vrgb) +value caml_gr_set_color(value vrgb) { int xcolor; - gr_check_open(); - grcolor = Int_val(vrgb); - if (grcolor >= 0 ){ - xcolor = gr_pixel_rgb(Int_val(vrgb)); - XSetForeground(grdisplay, grwindow.gc, xcolor); - XSetForeground(grdisplay, grbstore.gc, xcolor); + caml_gr_check_open(); + caml_gr_color = Int_val(vrgb); + if (caml_gr_color >= 0 ){ + xcolor = caml_gr_pixel_rgb(Int_val(vrgb)); + XSetForeground(caml_gr_display, caml_gr_window.gc, xcolor); + XSetForeground(caml_gr_display, caml_gr_bstore.gc, xcolor); } else { - XSetForeground(grdisplay, grwindow.gc, grbackground); - XSetForeground(grdisplay, grbstore.gc, grbackground); + XSetForeground(caml_gr_display, caml_gr_window.gc, caml_gr_background); + XSetForeground(caml_gr_display, caml_gr_bstore.gc, caml_gr_background); } return Val_unit; } diff --git a/otherlibs/graph/draw.c b/otherlibs/graph/draw.c index 18166168b..d73cb4706 100644 --- a/otherlibs/graph/draw.c +++ b/otherlibs/graph/draw.c @@ -16,63 +16,63 @@ #include "libgraph.h" #include <alloc.h> -value gr_plot(value vx, value vy) +value caml_gr_plot(value vx, value vy) { int x = Int_val(vx); int y = Int_val(vy); - gr_check_open(); - if(grremember_mode) - XDrawPoint(grdisplay, grbstore.win, grbstore.gc, x, Bcvt(y)); - if(grdisplay_mode) { - XDrawPoint(grdisplay, grwindow.win, grwindow.gc, x, Wcvt(y)); - XFlush(grdisplay); + caml_gr_check_open(); + if(caml_gr_remember_modeflag) + XDrawPoint(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, x, Bcvt(y)); + if(caml_gr_display_modeflag) { + XDrawPoint(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, x, Wcvt(y)); + XFlush(caml_gr_display); } return Val_unit; } -value gr_moveto(value vx, value vy) +value caml_gr_moveto(value vx, value vy) { - grx = Int_val(vx); - gry = Int_val(vy); + caml_gr_x = Int_val(vx); + caml_gr_y = Int_val(vy); return Val_unit; } -value gr_current_x(void) +value caml_gr_current_x(void) { - return Val_int(grx); + return Val_int(caml_gr_x); } -value gr_current_y(void) +value caml_gr_current_y(void) { - return Val_int(gry); + return Val_int(caml_gr_y); } -value gr_lineto(value vx, value vy) +value caml_gr_lineto(value vx, value vy) { int x = Int_val(vx); int y = Int_val(vy); - gr_check_open(); - if(grremember_mode) - XDrawLine(grdisplay, grbstore.win, grbstore.gc, - grx, Bcvt(gry), x, Bcvt(y)); - if(grdisplay_mode) { - XDrawLine(grdisplay, grwindow.win, grwindow.gc, - grx, Wcvt(gry), x, Wcvt(y)); - XFlush(grdisplay); + caml_gr_check_open(); + if(caml_gr_remember_modeflag) + XDrawLine(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, + caml_gr_x, Bcvt(caml_gr_y), x, Bcvt(y)); + if(caml_gr_display_modeflag) { + XDrawLine(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, + caml_gr_x, Wcvt(caml_gr_y), x, Wcvt(y)); + XFlush(caml_gr_display); } - grx = x; - gry = y; + caml_gr_x = x; + caml_gr_y = y; return Val_unit; } -value gr_draw_rect(value vx, value vy, value vw, value vh) +value caml_gr_draw_rect(value vx, value vy, value vw, value vh) { int x = Int_val(vx); int y = Int_val(vy); int w = Int_val(vw); int h = Int_val(vh); - gr_check_open(); + caml_gr_check_open(); y = Bcvt(y) - h + 1; /* Correct for XDrawRectangle irritating habit of drawing a larger rectangle hanging out one pixel below and to the right of the @@ -81,18 +81,18 @@ value gr_draw_rect(value vx, value vy, value vw, value vh) y += 1; w -= 1; h -= 1; - if(grremember_mode) - XDrawRectangle(grdisplay, grbstore.win, grbstore.gc, + if(caml_gr_remember_modeflag) + XDrawRectangle(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, x, y, w, h); - if(grdisplay_mode) { - XDrawRectangle(grdisplay, grwindow.win, grwindow.gc, + if(caml_gr_display_modeflag) { + XDrawRectangle(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, x, y, w, h); - XFlush(grdisplay); + XFlush(caml_gr_display); } return Val_unit; } -value gr_draw_arc_nat(value vx, value vy, value vrx, value vry, value va1, value va2) +value caml_gr_draw_arc_nat(value vx, value vy, value vrx, value vry, value va1, value va2) { int x = Int_val(vx); int y = Int_val(vy); @@ -101,31 +101,31 @@ value gr_draw_arc_nat(value vx, value vy, value vrx, value vry, value va1, value int a1 = Int_val(va1); int a2 = Int_val(va2); - gr_check_open(); - if(grremember_mode) - XDrawArc(grdisplay, grbstore.win, grbstore.gc, + caml_gr_check_open(); + if(caml_gr_remember_modeflag) + XDrawArc(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, x - rx, Bcvt(y) - ry, rx * 2, ry * 2, a1 * 64, (a2 - a1) * 64); - if(grdisplay_mode) { - XDrawArc(grdisplay, grwindow.win, grwindow.gc, + if(caml_gr_display_modeflag) { + XDrawArc(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, x - rx, Wcvt(y) - ry, rx * 2, ry * 2, a1 * 64, (a2 - a1) * 64); - XFlush(grdisplay); + XFlush(caml_gr_display); } return Val_unit; } -value gr_draw_arc(value *argv, int argc) +value caml_gr_draw_arc(value *argv, int argc) { - return gr_draw_arc_nat(argv[0], argv[1], argv[2], argv[3], argv[4], argv[5]); + return caml_gr_draw_arc_nat(argv[0], argv[1], argv[2], argv[3], argv[4], argv[5]); } -value gr_set_line_width(value vwidth) +value caml_gr_set_line_width(value vwidth) { int width = Int_val(vwidth); - gr_check_open(); - XSetLineAttributes(grdisplay, grwindow.gc, + caml_gr_check_open(); + XSetLineAttributes(caml_gr_display, caml_gr_window.gc, width, LineSolid, CapRound, JoinRound); - XSetLineAttributes(grdisplay, grbstore.gc, + XSetLineAttributes(caml_gr_display, caml_gr_bstore.gc, width, LineSolid, CapRound, JoinRound); return Val_unit; } diff --git a/otherlibs/graph/dump_img.c b/otherlibs/graph/dump_img.c index 75a9dce43..8c82c21bf 100644 --- a/otherlibs/graph/dump_img.c +++ b/otherlibs/graph/dump_img.c @@ -18,14 +18,14 @@ #include <alloc.h> #include <memory.h> -value gr_dump_image(value image) +value caml_gr_dump_image(value image) { int width, height, i, j; XImage * idata, * imask; value m = Val_unit; Begin_roots2(image, m); - gr_check_open(); + caml_gr_check_open(); width = Width_im(image); height = Height_im(image); m = alloc(height, 0); @@ -35,15 +35,15 @@ value gr_dump_image(value image) } idata = - XGetImage(grdisplay, Data_im(image), 0, 0, width, height, (-1), ZPixmap); + XGetImage(caml_gr_display, Data_im(image), 0, 0, width, height, (-1), ZPixmap); for (i = 0; i < height; i++) for (j = 0; j < width; j++) - Field(Field(m, i), j) = Val_int(gr_rgb_pixel(XGetPixel(idata, j, i))); + Field(Field(m, i), j) = Val_int(caml_gr_rgb_pixel(XGetPixel(idata, j, i))); XDestroyImage(idata); if (Mask_im(image) != None) { imask = - XGetImage(grdisplay, Mask_im(image), 0, 0, width, height, 1, ZPixmap); + XGetImage(caml_gr_display, Mask_im(image), 0, 0, width, height, 1, ZPixmap); for (i = 0; i < height; i++) for (j = 0; j < width; j++) if (XGetPixel(imask, j, i) == 0) diff --git a/otherlibs/graph/events.c b/otherlibs/graph/events.c index 1f0029d25..ca8827ee3 100644 --- a/otherlibs/graph/events.c +++ b/otherlibs/graph/events.c @@ -32,76 +32,76 @@ struct event_data { unsigned char key; }; -static struct event_data gr_queue[SIZE_QUEUE]; -static unsigned int gr_head = 0; /* position of next read */ -static unsigned int gr_tail = 0; /* position of next write */ +static struct event_data caml_gr_queue[SIZE_QUEUE]; +static unsigned int caml_gr_head = 0; /* position of next read */ +static unsigned int caml_gr_tail = 0; /* position of next write */ -#define QueueIsEmpty (gr_tail == gr_head) +#define QueueIsEmpty (caml_gr_tail == caml_gr_head) -static void gr_enqueue_event(int kind, int mouse_x, int mouse_y, +static void caml_gr_enqueue_event(int kind, int mouse_x, int mouse_y, int button, int key) { struct event_data * ev; - ev = &(gr_queue[gr_tail]); + ev = &(caml_gr_queue[caml_gr_tail]); ev->kind = kind; ev->mouse_x = mouse_x; ev->mouse_y = mouse_y; ev->button = (button != 0); ev->key = key; - gr_tail = (gr_tail + 1) % SIZE_QUEUE; + caml_gr_tail = (caml_gr_tail + 1) % SIZE_QUEUE; /* If queue was full, it now appears empty; drop oldest entry from queue. */ - if (QueueIsEmpty) gr_head = (gr_head + 1) % SIZE_QUEUE; + if (QueueIsEmpty) caml_gr_head = (caml_gr_head + 1) % SIZE_QUEUE; } #define BUTTON_STATE(state) \ ((state) & (Button1Mask|Button2Mask|Button3Mask|Button4Mask|Button5Mask)) -void gr_handle_event(XEvent * event) +void caml_gr_handle_event(XEvent * event) { switch (event->type) { case Expose: - XCopyArea(grdisplay, grbstore.win, grwindow.win, grwindow.gc, - event->xexpose.x, event->xexpose.y + grbstore.h - grwindow.h, + XCopyArea(caml_gr_display, caml_gr_bstore.win, caml_gr_window.win, caml_gr_window.gc, + event->xexpose.x, event->xexpose.y + caml_gr_bstore.h - caml_gr_window.h, event->xexpose.width, event->xexpose.height, event->xexpose.x, event->xexpose.y); - XFlush(grdisplay); + XFlush(caml_gr_display); break; case ConfigureNotify: - grwindow.w = event->xconfigure.width; - grwindow.h = event->xconfigure.height; - if (grwindow.w > grbstore.w || grwindow.h > grbstore.h) { + caml_gr_window.w = event->xconfigure.width; + caml_gr_window.h = event->xconfigure.height; + if (caml_gr_window.w > caml_gr_bstore.w || caml_gr_window.h > caml_gr_bstore.h) { /* Allocate a new backing store large enough to accomodate both the old backing store and the current window. */ struct canvas newbstore; - newbstore.w = max(grwindow.w, grbstore.w); - newbstore.h = max(grwindow.h, grbstore.h); + newbstore.w = max(caml_gr_window.w, caml_gr_bstore.w); + newbstore.h = max(caml_gr_window.h, caml_gr_bstore.h); newbstore.win = - XCreatePixmap(grdisplay, grwindow.win, newbstore.w, newbstore.h, - XDefaultDepth(grdisplay, grscreen)); - newbstore.gc = XCreateGC(grdisplay, newbstore.win, 0, NULL); - XSetBackground(grdisplay, newbstore.gc, grwhite); - XSetForeground(grdisplay, newbstore.gc, grwhite); - XFillRectangle(grdisplay, newbstore.win, newbstore.gc, + XCreatePixmap(caml_gr_display, caml_gr_window.win, newbstore.w, newbstore.h, + XDefaultDepth(caml_gr_display, caml_gr_screen)); + newbstore.gc = XCreateGC(caml_gr_display, newbstore.win, 0, NULL); + XSetBackground(caml_gr_display, newbstore.gc, caml_gr_white); + XSetForeground(caml_gr_display, newbstore.gc, caml_gr_white); + XFillRectangle(caml_gr_display, newbstore.win, newbstore.gc, 0, 0, newbstore.w, newbstore.h); - XSetForeground(grdisplay, newbstore.gc, grcolor); - if (grfont != NULL) - XSetFont(grdisplay, newbstore.gc, grfont->fid); + XSetForeground(caml_gr_display, newbstore.gc, caml_gr_color); + if (caml_gr_font != NULL) + XSetFont(caml_gr_display, newbstore.gc, caml_gr_font->fid); /* Copy the old backing store into the new one */ - XCopyArea(grdisplay, grbstore.win, newbstore.win, newbstore.gc, - 0, 0, grbstore.w, grbstore.h, 0, newbstore.h - grbstore.h); + XCopyArea(caml_gr_display, caml_gr_bstore.win, newbstore.win, newbstore.gc, + 0, 0, caml_gr_bstore.w, caml_gr_bstore.h, 0, newbstore.h - caml_gr_bstore.h); /* Free the old backing store */ - XFreeGC(grdisplay, grbstore.gc); - XFreePixmap(grdisplay, grbstore.win); + XFreeGC(caml_gr_display, caml_gr_bstore.gc); + XFreePixmap(caml_gr_display, caml_gr_bstore.win); /* Use the new backing store */ - grbstore = newbstore; - XFlush(grdisplay); + caml_gr_bstore = newbstore; + XFlush(caml_gr_display); } break; @@ -117,25 +117,25 @@ void gr_handle_event(XEvent * event) nchars = XLookupString(&(event->xkey), keytxt, sizeof(keytxt), &thekey, 0); for (p = keytxt; nchars > 0; p++, nchars--) - gr_enqueue_event(event->type, event->xkey.x, event->xkey.y, + caml_gr_enqueue_event(event->type, event->xkey.x, event->xkey.y, BUTTON_STATE(event->xkey.state), *p); break; } case ButtonPress: case ButtonRelease: - gr_enqueue_event(event->type, event->xbutton.x, event->xbutton.y, + caml_gr_enqueue_event(event->type, event->xbutton.x, event->xbutton.y, event->type == ButtonPress, 0); break; case MotionNotify: - gr_enqueue_event(event->type, event->xmotion.x, event->xmotion.y, + caml_gr_enqueue_event(event->type, event->xmotion.x, event->xmotion.y, BUTTON_STATE(event->xmotion.state), 0); break; } } -static value gr_wait_allocate_result(int mouse_x, int mouse_y, int button, +static value caml_gr_wait_allocate_result(int mouse_x, int mouse_y, int button, int keypressed, int key) { value res = alloc_small(5, 0); @@ -147,7 +147,7 @@ static value gr_wait_allocate_result(int mouse_x, int mouse_y, int button, return res; } -static value gr_wait_event_poll(void) +static value caml_gr_wait_event_poll(void) { int mouse_x, mouse_y, button, key, keypressed; Window rootwin, childwin; @@ -155,7 +155,7 @@ static value gr_wait_event_poll(void) unsigned int modifiers; unsigned int i; - if (XQueryPointer(grdisplay, grwindow.win, + if (XQueryPointer(caml_gr_display, caml_gr_window.win, &rootwin, &childwin, &root_x, &root_y, &win_x, &win_y, &modifiers)) { @@ -170,35 +170,35 @@ static value gr_wait_event_poll(void) /* Look inside event queue for pending KeyPress events */ key = 0; keypressed = False; - for (i = gr_head; i != gr_tail; i = (i + 1) % SIZE_QUEUE) { - if (gr_queue[i].kind == KeyPress) { + for (i = caml_gr_head; i != caml_gr_tail; i = (i + 1) % SIZE_QUEUE) { + if (caml_gr_queue[i].kind == KeyPress) { keypressed = True; - key = gr_queue[i].key; + key = caml_gr_queue[i].key; break; } } - return gr_wait_allocate_result(mouse_x, mouse_y, button, keypressed, key); + return caml_gr_wait_allocate_result(mouse_x, mouse_y, button, keypressed, key); } -static value gr_wait_event_in_queue(long mask) +static value caml_gr_wait_event_in_queue(long mask) { struct event_data * ev; /* Pop events in queue until one matches mask. */ - while (gr_head != gr_tail) { - ev = &(gr_queue[gr_head]); - gr_head = (gr_head + 1) % SIZE_QUEUE; + while (caml_gr_head != caml_gr_tail) { + ev = &(caml_gr_queue[caml_gr_head]); + caml_gr_head = (caml_gr_head + 1) % SIZE_QUEUE; if ((ev->kind == KeyPress && (mask & KeyPressMask)) || (ev->kind == ButtonPress && (mask & ButtonPressMask)) || (ev->kind == ButtonRelease && (mask & ButtonReleaseMask)) || (ev->kind == MotionNotify && (mask & PointerMotionMask))) - return gr_wait_allocate_result(ev->mouse_x, ev->mouse_y, + return caml_gr_wait_allocate_result(ev->mouse_x, ev->mouse_y, ev->button, ev->kind == KeyPress, ev->key); } return Val_false; } -static value gr_wait_event_blocking(long mask) +static value caml_gr_wait_event_blocking(long mask) { #ifdef POSIX_SIGNALS sigset_t sigset; @@ -210,13 +210,13 @@ static value gr_wait_event_blocking(long mask) value res; /* First see if we have a matching event in the queue */ - res = gr_wait_event_in_queue(mask); + res = caml_gr_wait_event_in_queue(mask); if (res != Val_false) return res; /* Increase the selected events if required */ - if ((mask & ~grselected_events) != 0) { - grselected_events |= mask; - XSelectInput(grdisplay, grwindow.win, grselected_events); + if ((mask & ~caml_gr_selected_events) != 0) { + caml_gr_selected_events |= mask; + XSelectInput(caml_gr_display, caml_gr_window.win, caml_gr_selected_events); } /* Block or deactivate the EVENT signal */ @@ -230,16 +230,16 @@ static value gr_wait_event_blocking(long mask) /* Replenish our event queue from that of X11 */ while (1) { - if (XCheckMaskEvent(grdisplay, -1 /*all events*/, &event)) { + if (XCheckMaskEvent(caml_gr_display, -1 /*all events*/, &event)) { /* One event available: add it to our queue */ - gr_handle_event(&event); + caml_gr_handle_event(&event); /* See if we now have a matching event */ - res = gr_wait_event_in_queue(mask); + res = caml_gr_wait_event_in_queue(mask); if (res != Val_false) break; } else { /* No event available: block on input socket until one is */ FD_ZERO(&readfds); - FD_SET(ConnectionNumber(grdisplay), &readfds); + FD_SET(ConnectionNumber(caml_gr_display), &readfds); enter_blocking_section(); select(FD_SETSIZE, &readfds, NULL, NULL, NULL); leave_blocking_section(); @@ -257,12 +257,12 @@ static value gr_wait_event_blocking(long mask) return res; } -value gr_wait_event(value eventlist) /* ML */ +value caml_gr_wait_event(value eventlist) /* ML */ { int mask; Bool poll; - gr_check_open(); + caml_gr_check_open(); mask = 0; poll = False; while (eventlist != Val_int(0)) { @@ -281,7 +281,7 @@ value gr_wait_event(value eventlist) /* ML */ eventlist = Field(eventlist, 1); } if (poll) - return gr_wait_event_poll(); + return caml_gr_wait_event_poll(); else - return gr_wait_event_blocking(mask); + return caml_gr_wait_event_blocking(mask); } diff --git a/otherlibs/graph/fill.c b/otherlibs/graph/fill.c index faaa3c4cf..1982fe4b5 100644 --- a/otherlibs/graph/fill.c +++ b/otherlibs/graph/fill.c @@ -16,52 +16,52 @@ #include "libgraph.h" #include <memory.h> -value gr_fill_rect(value vx, value vy, value vw, value vh) +value caml_gr_fill_rect(value vx, value vy, value vw, value vh) { int x = Int_val(vx); int y = Int_val(vy); int w = Int_val(vw); int h = Int_val(vh); - gr_check_open(); - if(grremember_mode) - XFillRectangle(grdisplay, grbstore.win, grbstore.gc, + caml_gr_check_open(); + if(caml_gr_remember_modeflag) + XFillRectangle(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, x, Bcvt(y) - h + 1, w, h); - if(grdisplay_mode) { - XFillRectangle(grdisplay, grwindow.win, grwindow.gc, + if(caml_gr_display_modeflag) { + XFillRectangle(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, x, Wcvt(y) - h + 1, w, h); - XFlush(grdisplay); + XFlush(caml_gr_display); } return Val_unit; } -value gr_fill_poly(value array) +value caml_gr_fill_poly(value array) { XPoint * points; int npoints, i; - gr_check_open(); + caml_gr_check_open(); npoints = Wosize_val(array); points = (XPoint *) stat_alloc(npoints * sizeof(XPoint)); for (i = 0; i < npoints; i++) { points[i].x = Int_val(Field(Field(array, i), 0)); points[i].y = Bcvt(Int_val(Field(Field(array, i), 1))); } - if(grremember_mode) - XFillPolygon(grdisplay, grbstore.win, grbstore.gc, points, + if(caml_gr_remember_modeflag) + XFillPolygon(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, points, npoints, Complex, CoordModeOrigin); - if(grdisplay_mode) { + if(caml_gr_display_modeflag) { for (i = 0; i < npoints; i++) points[i].y = BtoW(points[i].y); - XFillPolygon(grdisplay, grwindow.win, grwindow.gc, points, + XFillPolygon(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, points, npoints, Complex, CoordModeOrigin); - XFlush(grdisplay); + XFlush(caml_gr_display); } stat_free((char *) points); return Val_unit; } -value gr_fill_arc_nat(value vx, value vy, value vrx, value vry, value va1, value va2) +value caml_gr_fill_arc_nat(value vx, value vy, value vrx, value vry, value va1, value va2) { int x = Int_val(vx); int y = Int_val(vy); @@ -70,19 +70,19 @@ value gr_fill_arc_nat(value vx, value vy, value vrx, value vry, value va1, value int a1 = Int_val(va1); int a2 = Int_val(va2); - gr_check_open(); - if(grremember_mode) - XFillArc(grdisplay, grbstore.win, grbstore.gc, + caml_gr_check_open(); + if(caml_gr_remember_modeflag) + XFillArc(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, x - rx, Bcvt(y) - ry, rx * 2, ry * 2, a1 * 64, (a2 - a1) * 64); - if(grdisplay_mode) { - XFillArc(grdisplay, grwindow.win, grwindow.gc, + if(caml_gr_display_modeflag) { + XFillArc(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, x - rx, Wcvt(y) - ry, rx * 2, ry * 2, a1 * 64, (a2 - a1) * 64); - XFlush(grdisplay); + XFlush(caml_gr_display); } return Val_unit; } -value gr_fill_arc(value *argv, int argc) +value caml_gr_fill_arc(value *argv, int argc) { - return gr_fill_arc_nat(argv[0], argv[1], argv[2], argv[3], argv[4], argv[5]); + return caml_gr_fill_arc_nat(argv[0], argv[1], argv[2], argv[3], argv[4], argv[5]); } diff --git a/otherlibs/graph/graphics.ml b/otherlibs/graph/graphics.ml index 88e7450e0..fa2d59a38 100644 --- a/otherlibs/graph/graphics.ml +++ b/otherlibs/graph/graphics.ml @@ -20,10 +20,10 @@ exception Graphic_failure of string let _ = Callback.register_exception "Graphics.Graphic_failure" (Graphic_failure "") -external raw_open_graph: string -> unit = "gr_open_graph" -external raw_close_graph: unit -> unit = "gr_close_graph" -external sigio_signal: unit -> int = "gr_sigio_signal" -external sigio_handler: int -> unit = "gr_sigio_handler" +external raw_open_graph: string -> unit = "caml_gr_open_graph" +external raw_close_graph: unit -> unit = "caml_gr_close_graph" +external sigio_signal: unit -> int = "caml_gr_sigio_signal" +external sigio_handler: int -> unit = "caml_gr_sigio_handler" let unix_open_graph arg = Sys.set_signal (sigio_signal()) (Sys.Signal_handle sigio_handler); @@ -40,16 +40,16 @@ let (open_graph, close_graph) = | "MacOS" -> (raw_open_graph, raw_close_graph) | _ -> invalid_arg ("Graphics: unknown OS type: " ^ Sys.os_type) -external set_window_title : string -> unit = "gr_set_window_title" -external clear_graph : unit -> unit = "gr_clear_graph" -external size_x : unit -> int = "gr_size_x" -external size_y : unit -> int = "gr_size_y" +external set_window_title : string -> unit = "caml_gr_set_window_title" +external clear_graph : unit -> unit = "caml_gr_clear_graph" +external size_x : unit -> int = "caml_gr_size_x" +external size_y : unit -> int = "caml_gr_size_y" (* Double-buffering *) -external display_mode : bool -> unit = "gr_display_mode" -external remember_mode : bool -> unit = "gr_remember_mode" -external synchronize : unit -> unit = "gr_synchronize" +external display_mode : bool -> unit = "caml_gr_display_mode" +external remember_mode : bool -> unit = "caml_gr_remember_mode" +external synchronize : unit -> unit = "caml_gr_synchronize" let auto_synchronize = function | true -> display_mode true; remember_mode true; synchronize () @@ -63,7 +63,7 @@ type color = int let rgb r g b = (r lsl 16) + (g lsl 8) + b -external set_color : color -> unit = "gr_set_color" +external set_color : color -> unit = "caml_gr_set_color" let black = 0x000000 and white = 0xFFFFFF @@ -79,22 +79,22 @@ and foreground = black (* Drawing *) -external plot : int -> int -> unit = "gr_plot" +external plot : int -> int -> unit = "caml_gr_plot" let plots points = for i = 0 to Array.length points - 1 do let (x, y) = points.(i) in plot x y; done ;; -external point_color : int -> int -> color = "gr_point_color" -external moveto : int -> int -> unit = "gr_moveto" -external current_x : unit -> int = "gr_current_x" -external current_y : unit -> int = "gr_current_y" +external point_color : int -> int -> color = "caml_gr_point_color" +external moveto : int -> int -> unit = "caml_gr_moveto" +external current_x : unit -> int = "caml_gr_current_x" +external current_y : unit -> int = "caml_gr_current_y" let current_point () = current_x (), current_y () -external lineto : int -> int -> unit = "gr_lineto" +external lineto : int -> int -> unit = "caml_gr_lineto" let rlineto x y = lineto (current_x () + x) (current_y () + y) let rmoveto x y = moveto (current_x () + x) (current_y () + y) -external draw_rect : int -> int -> int -> int -> unit = "gr_draw_rect" +external draw_rect : int -> int -> int -> int -> unit = "caml_gr_draw_rect" let draw_poly, draw_poly_line = let dodraw close_flag points = if Array.length points > 0 then begin @@ -119,25 +119,25 @@ let draw_segments segs = moveto savex savey; ;; external draw_arc : int -> int -> int -> int -> int -> int -> unit - = "gr_draw_arc" "gr_draw_arc_nat" + = "caml_gr_draw_arc" "caml_gr_draw_arc_nat" let draw_ellipse x y rx ry = draw_arc x y rx ry 0 360 let draw_circle x y r = draw_arc x y r r 0 360 -external set_line_width : int -> unit = "gr_set_line_width" +external set_line_width : int -> unit = "caml_gr_set_line_width" -external fill_rect : int -> int -> int -> int -> unit = "gr_fill_rect" -external fill_poly : (int * int) array -> unit = "gr_fill_poly" +external fill_rect : int -> int -> int -> int -> unit = "caml_gr_fill_rect" +external fill_poly : (int * int) array -> unit = "caml_gr_fill_poly" external fill_arc : int -> int -> int -> int -> int -> int -> unit - = "gr_fill_arc" "gr_fill_arc_nat" + = "caml_gr_fill_arc" "caml_gr_fill_arc_nat" let fill_ellipse x y rx ry = fill_arc x y rx ry 0 360 let fill_circle x y r = fill_arc x y r r 0 360 (* Text *) -external draw_char : char -> unit = "gr_draw_char" -external draw_string : string -> unit = "gr_draw_string" -external set_font : string -> unit = "gr_set_font" -external set_text_size : int -> unit = "gr_set_text_size" -external text_size : string -> int * int = "gr_text_size" +external draw_char : char -> unit = "caml_gr_draw_char" +external draw_string : string -> unit = "caml_gr_draw_string" +external set_font : string -> unit = "caml_gr_set_font" +external set_text_size : int -> unit = "caml_gr_set_text_size" +external text_size : string -> int * int = "caml_gr_text_size" (* Images *) @@ -145,11 +145,11 @@ type image let transp = -1 -external make_image : color array array -> image = "gr_make_image" -external dump_image : image -> color array array = "gr_dump_image" -external draw_image : image -> int -> int -> unit = "gr_draw_image" -external create_image : int -> int -> image = "gr_create_image" -external blit_image : image -> int -> int -> unit = "gr_blit_image" +external make_image : color array array -> image = "caml_gr_make_image" +external dump_image : image -> color array array = "caml_gr_dump_image" +external draw_image : image -> int -> int -> unit = "caml_gr_draw_image" +external create_image : int -> int -> image = "caml_gr_create_image" +external blit_image : image -> int -> int -> unit = "caml_gr_blit_image" let get_image x y w h = let image = create_image w h in @@ -172,7 +172,7 @@ type event = | Mouse_motion | Poll -external wait_next_event : event list -> status = "gr_wait_event" +external wait_next_event : event list -> status = "caml_gr_wait_event" let mouse_pos () = let e = wait_next_event [Poll] in (e.mouse_x, e.mouse_y) @@ -188,7 +188,7 @@ let key_pressed () = (*** Sound *) -external sound : int -> int -> unit = "gr_sound" +external sound : int -> int -> unit = "caml_gr_sound" (* Splines *) let add (x1, y1) (x2, y2) = (x1 +. x2, y1 +. y2) diff --git a/otherlibs/graph/graphics.mli b/otherlibs/graph/graphics.mli index ff271ce55..219ad7107 100644 --- a/otherlibs/graph/graphics.mli +++ b/otherlibs/graph/graphics.mli @@ -35,13 +35,13 @@ val close_graph : unit -> unit val set_window_title : string -> unit (** Set the title of the graphics window. *) -external clear_graph : unit -> unit = "gr_clear_graph" +external clear_graph : unit -> unit = "caml_gr_clear_graph" (** Erase the graphics window. *) -external size_x : unit -> int = "gr_size_x" +external size_x : unit -> int = "caml_gr_size_x" (** See {!Graphics.size_y}. *) -external size_y : unit -> int = "gr_size_y" +external size_y : unit -> int = "caml_gr_size_y" (** Return the size of the graphics window. Coordinates of the screen pixels range over [0 .. size_x()-1] and [0 .. size_y()-1]. Drawings outside of this rectangle are clipped, without causing @@ -61,7 +61,7 @@ val rgb : int -> int -> int -> color component [r], green component [g], and blue component [b]. [r], [g] and [b] are in the range [0..255]. *) -external set_color : color -> unit = "gr_set_color" +external set_color : color -> unit = "caml_gr_set_color" (** Set the current drawing color. *) val background : color @@ -89,32 +89,32 @@ val magenta : color (** {6 Point and line drawing} *) -external plot : int -> int -> unit = "gr_plot" +external plot : int -> int -> unit = "caml_gr_plot" (** Plot the given point with the current drawing color. *) val plots : (int * int) array -> unit (** Plot the given points with the current drawing color. *) -external point_color : int -> int -> color = "gr_point_color" +external point_color : int -> int -> color = "caml_gr_point_color" (** Return the color of the given point in the backing store (see "Double buffering" below). *) -external moveto : int -> int -> unit = "gr_moveto" +external moveto : int -> int -> unit = "caml_gr_moveto" (** Position the current point. *) val rmoveto : int -> int -> unit (** [rmoveto dx dy] translates the current point by the given vector. *) -external current_x : unit -> int = "gr_current_x" +external current_x : unit -> int = "caml_gr_current_x" (** Return the abscissa of the current point. *) -external current_y : unit -> int = "gr_current_y" +external current_y : unit -> int = "caml_gr_current_y" (** Return the ordinate of the current point. *) val current_point : unit -> int * int (** Return the position of the current point. *) -external lineto : int -> int -> unit = "gr_lineto" +external lineto : int -> int -> unit = "caml_gr_lineto" (** Draw a line with endpoints the current point and the given point, and move the current point to the given point. *) @@ -128,7 +128,7 @@ val curveto : int * int -> int * int -> int * int -> unit the current point to point [d], with control points [b] and [c], and moves the current point to [d]. *) -external draw_rect : int -> int -> int -> int -> unit = "gr_draw_rect" +external draw_rect : int -> int -> int -> int -> unit = "caml_gr_draw_rect" (** [draw_rect x y w h] draws the rectangle with lower left corner at [x,y], width [w] and height [h]. The current point is unchanged. *) @@ -155,7 +155,7 @@ val draw_segments : (int * int * int * int) array -> unit external draw_arc : int -> int -> int -> int -> int -> int -> - unit = "gr_draw_arc" "gr_draw_arc_nat" + unit = "caml_gr_draw_arc" "caml_gr_draw_arc_nat" (** [draw_arc x y rx ry a1 a2] draws an elliptical arc with center [x,y], horizontal radius [rx], vertical radius [ry], from angle [a1] to angle [a2] (in degrees). The current point is unchanged. *) @@ -169,7 +169,7 @@ val draw_circle : int -> int -> int -> unit (** [draw_circle x y r] draws a circle with center [x,y] and radius [r]. The current point is unchanged. *) -external set_line_width : int -> unit = "gr_set_line_width" +external set_line_width : int -> unit = "caml_gr_set_line_width" (** Set the width of points and lines drawn with the functions above. Under X Windows, [set_line_width 0] selects a width of 1 pixel and a faster, but less precise drawing algorithm than the one @@ -177,15 +177,15 @@ external set_line_width : int -> unit = "gr_set_line_width" (** {6 Text drawing} *) -external draw_char : char -> unit = "gr_draw_char" +external draw_char : char -> unit = "caml_gr_draw_char" (** See {!Graphics.draw_string}.*) -external draw_string : string -> unit = "gr_draw_string" +external draw_string : string -> unit = "caml_gr_draw_string" (** Draw a character or a character string with lower left corner at current position. After drawing, the current position is set to the lower right corner of the text drawn. *) -external set_font : string -> unit = "gr_set_font" +external set_font : string -> unit = "caml_gr_set_font" (** Set the font used for drawing text. The interpretation of the arguments to [set_font] is implementation-dependent. *) @@ -195,24 +195,24 @@ val set_text_size : int -> unit The interpretation of the arguments to [set_text_size] is implementation-dependent. *) -external text_size : string -> int * int = "gr_text_size" +external text_size : string -> int * int = "caml_gr_text_size" (** Return the dimensions of the given text, if it were drawn with the current font and size. *) (** {6 Filling} *) -external fill_rect : int -> int -> int -> int -> unit = "gr_fill_rect" +external fill_rect : int -> int -> int -> int -> unit = "caml_gr_fill_rect" (** [fill_rect x y w h] fills the rectangle with lower left corner at [x,y], width [w] and height [h], with the current color. *) -external fill_poly : (int * int) array -> unit = "gr_fill_poly" +external fill_poly : (int * int) array -> unit = "caml_gr_fill_poly" (** Fill the given polygon with the current color. The array contains the coordinates of the vertices of the polygon. *) external fill_arc : int -> int -> int -> int -> int -> int -> - unit = "gr_fill_arc" "gr_fill_arc_nat" + unit = "caml_gr_fill_arc" "caml_gr_fill_arc_nat" (** Fill an elliptical pie slice with the current color. The parameters are the same as for {!Graphics.draw_arc}. *) @@ -239,29 +239,29 @@ val transp : color of the corresponding point in the image. This allows superimposing an image over an existing background. *) -external make_image : color array array -> image = "gr_make_image" +external make_image : color array array -> image = "caml_gr_make_image" (** Convert the given color matrix to an image. Each sub-array represents one horizontal line. All sub-arrays must have the same length; otherwise, exception [Graphic_failure] is raised. *) -external dump_image : image -> color array array = "gr_dump_image" +external dump_image : image -> color array array = "caml_gr_dump_image" (** Convert an image to a color matrix. *) -external draw_image : image -> int -> int -> unit = "gr_draw_image" +external draw_image : image -> int -> int -> unit = "caml_gr_draw_image" (** Draw the given image with lower left corner at the given point. *) val get_image : int -> int -> int -> int -> image (** Capture the contents of a rectangle on the screen as an image. The parameters are the same as for {!Graphics.fill_rect}. *) -external create_image : int -> int -> image = "gr_create_image" +external create_image : int -> int -> image = "caml_gr_create_image" (** [create_image w h] returns a new image [w] pixels wide and [h] pixels tall, to be used in conjunction with [blit_image]. The initial image contents are random, except that no point is transparent. *) -external blit_image : image -> int -> int -> unit = "gr_blit_image" +external blit_image : image -> int -> int -> unit = "caml_gr_blit_image" (** [blit_image img x y] copies screen pixels into the image [img], modifying [img] in-place. The pixels copied are those inside the rectangle with lower left corner at [x,y], and width and height @@ -290,7 +290,7 @@ type event = (** To specify events to wait for. *) -external wait_next_event : event list -> status = "gr_wait_event" +external wait_next_event : event list -> status = "caml_gr_wait_event" (** Wait until one of the events specified in the given event list occurs, and return the status of the mouse and keyboard at that time. If [Poll] is given in the event list, return immediately @@ -322,7 +322,7 @@ val key_pressed : unit -> bool (** {6 Sound} *) -external sound : int -> int -> unit = "gr_sound" +external sound : int -> int -> unit = "caml_gr_sound" (** [sound freq dur] plays a sound at frequency [freq] (in hertz) for a duration [dur] (in milliseconds). *) @@ -350,13 +350,13 @@ val auto_synchronize : bool -> unit The default drawing mode corresponds to [auto_synchronize true]. *) -external synchronize : unit -> unit = "gr_synchronize" +external synchronize : unit -> unit = "caml_gr_synchronize" (** Synchronize the backing store and the on-screen window, by copying the contents of the backing store onto the graphics window. *) -external display_mode : bool -> unit = "gr_display_mode" +external display_mode : bool -> unit = "caml_gr_display_mode" (** Set display mode on or off. When turned on, drawings are done in the graphics window; when turned off, drawings do not affect the graphics window. This occurs independently of @@ -364,7 +364,7 @@ external display_mode : bool -> unit = "gr_display_mode" below). Default display mode is on. *) -external remember_mode : bool -> unit = "gr_remember_mode" +external remember_mode : bool -> unit = "caml_gr_remember_mode" (** Set remember mode on or off. When turned on, drawings are done in the backing store; when turned off, the backing store is unaffected by drawings. This occurs independently of drawing diff --git a/otherlibs/graph/graphicsX11.ml b/otherlibs/graph/graphicsX11.ml index 69f7b718d..5b0b759fe 100644 --- a/otherlibs/graph/graphicsX11.ml +++ b/otherlibs/graph/graphicsX11.ml @@ -17,14 +17,14 @@ type window_id = string -external window_id : unit -> window_id = "gr_window_id" +external window_id : unit -> window_id = "caml_gr_window_id" let subwindows = Hashtbl.create 13 external open_subwindow : int -> int -> int -> int -> window_id - = "gr_open_subwindow" + = "caml_gr_open_subwindow" external close_subwindow : window_id -> unit - = "gr_close_subwindow" + = "caml_gr_close_subwindow" let open_subwindow ~x ~y ~width ~height = let wid = open_subwindow x y width height in diff --git a/otherlibs/graph/image.c b/otherlibs/graph/image.c index 8d47fc4e5..501398b35 100644 --- a/otherlibs/graph/image.c +++ b/otherlibs/graph/image.c @@ -18,15 +18,15 @@ #include <alloc.h> #include <custom.h> -static void gr_free_image(value im) +static void caml_gr_free_image(value im) { - XFreePixmap(grdisplay, Data_im(im)); - if (Mask_im(im) != None) XFreePixmap(grdisplay, Mask_im(im)); + XFreePixmap(caml_gr_display, Data_im(im)); + if (Mask_im(im) != None) XFreePixmap(caml_gr_display, Mask_im(im)); } static struct custom_operations image_ops = { "_image", - gr_free_image, + caml_gr_free_image, custom_compare_default, custom_hash_default, custom_serialize_default, @@ -35,71 +35,73 @@ static struct custom_operations image_ops = { #define Max_image_mem 2000000 -value gr_new_image(int w, int h) +value caml_gr_new_image(int w, int h) { value res = alloc_custom(&image_ops, sizeof(struct grimage), w * h, Max_image_mem); Width_im(res) = w; Height_im(res) = h; - Data_im(res) = XCreatePixmap(grdisplay, grwindow.win, w, h, - XDefaultDepth(grdisplay, grscreen)); + Data_im(res) = XCreatePixmap(caml_gr_display, caml_gr_window.win, w, h, + XDefaultDepth(caml_gr_display, caml_gr_screen)); Mask_im(res) = None; return res; } -value gr_create_image(value vw, value vh) +value caml_gr_create_image(value vw, value vh) { - gr_check_open(); - return gr_new_image(Int_val(vw), Int_val(vh)); + caml_gr_check_open(); + return caml_gr_new_image(Int_val(vw), Int_val(vh)); } -value gr_blit_image(value im, value vx, value vy) +value caml_gr_blit_image(value im, value vx, value vy) { int x = Int_val(vx); int y = Int_val(vy); - gr_check_open(); - XCopyArea(grdisplay, grbstore.win, Data_im(im), grbstore.gc, + caml_gr_check_open(); + XCopyArea(caml_gr_display, caml_gr_bstore.win, Data_im(im), caml_gr_bstore.gc, x, Bcvt(y) + 1 - Height_im(im), Width_im(im), Height_im(im), 0, 0); return Val_unit; } -value gr_draw_image(value im, value vx, value vy) +value caml_gr_draw_image(value im, value vx, value vy) { int x = Int_val(vx); int y = Int_val(vy); int wy = Wcvt(y) + 1 - Height_im(im); int by = Bcvt(y) + 1 - Height_im(im); - gr_check_open(); + caml_gr_check_open(); if (Mask_im(im) != None) { - if(grremember_mode) { - XSetClipOrigin(grdisplay, grbstore.gc, x, by); - XSetClipMask(grdisplay, grbstore.gc, Mask_im(im)); + if(caml_gr_remember_modeflag) { + XSetClipOrigin(caml_gr_display, caml_gr_bstore.gc, x, by); + XSetClipMask(caml_gr_display, caml_gr_bstore.gc, Mask_im(im)); } - if(grdisplay_mode) { - XSetClipOrigin(grdisplay, grwindow.gc, x, wy); - XSetClipMask(grdisplay, grwindow.gc, Mask_im(im)); + if(caml_gr_display_modeflag) { + XSetClipOrigin(caml_gr_display, caml_gr_window.gc, x, wy); + XSetClipMask(caml_gr_display, caml_gr_window.gc, Mask_im(im)); } } - if(grremember_mode) - XCopyArea(grdisplay, Data_im(im), grbstore.win, grbstore.gc, + if(caml_gr_remember_modeflag) + XCopyArea(caml_gr_display, Data_im(im), caml_gr_bstore.win, caml_gr_bstore.gc, 0, 0, Width_im(im), Height_im(im), x, by); - if(grdisplay_mode) - XCopyArea(grdisplay, Data_im(im), grwindow.win, grwindow.gc, + if(caml_gr_display_modeflag) + XCopyArea(caml_gr_display, Data_im(im), caml_gr_window.win, caml_gr_window.gc, 0, 0, Width_im(im), Height_im(im), x, wy); if (Mask_im(im) != None) { - if(grremember_mode) - XSetClipMask(grdisplay, grbstore.gc, None); - if(grdisplay_mode) - XSetClipMask(grdisplay, grwindow.gc, None); + if(caml_gr_remember_modeflag) + XSetClipMask(caml_gr_display, caml_gr_bstore.gc, None); + if(caml_gr_display_modeflag) + XSetClipMask(caml_gr_display, caml_gr_window.gc, None); } - if(grdisplay_mode) - XFlush(grdisplay); + if(caml_gr_display_modeflag) + XFlush(caml_gr_display); return Val_unit; } + +/* eof $Id$ */ diff --git a/otherlibs/graph/image.h b/otherlibs/graph/image.h index 441da97fb..539cf9f8c 100644 --- a/otherlibs/graph/image.h +++ b/otherlibs/graph/image.h @@ -26,4 +26,4 @@ struct grimage { #define Transparent (-1) -value gr_new_image(int w, int h); +value caml_gr_new_image(int w, int h); diff --git a/otherlibs/graph/libgraph.h b/otherlibs/graph/libgraph.h index 605c5a463..388f3c838 100644 --- a/otherlibs/graph/libgraph.h +++ b/otherlibs/graph/libgraph.h @@ -24,30 +24,30 @@ struct canvas { GC gc; /* The associated graphics context */ }; -extern Display * grdisplay; /* The display connection */ -extern int grscreen; /* The screen number */ -extern Colormap grcolormap; /* The color map */ -extern struct canvas grwindow; /* The graphics window */ -extern struct canvas grbstore; /* The pixmap used for backing store */ -extern int grwhite, grblack; /* Black and white pixels for X */ -extern int grbackground; /* Background color for X +extern Display * caml_gr_display; /* The display connection */ +extern int caml_gr_screen; /* The screen number */ +extern Colormap caml_gr_colormap; /* The color map */ +extern struct canvas caml_gr_window; /* The graphics window */ +extern struct canvas caml_gr_bstore; /* The pixmap used for backing store */ +extern int caml_gr_white, caml_gr_black; /* Black and white pixels for X */ +extern int caml_gr_background; /* Background color for X (used for CAML color -1) */ -extern Bool grdisplay_mode; /* Display-mode flag */ -extern Bool grremember_mode; /* Remember-mode flag */ -extern int grx, gry; /* Coordinates of the current point */ -extern int grcolor; /* Current *CAML* drawing color (can be -1) */ -extern XFontStruct * grfont; /* Current font */ -extern long grselected_events; /* Events we are interested in */ +extern Bool caml_gr_display_modeflag; /* Display-mode flag */ +extern Bool caml_gr_remember_modeflag; /* Remember-mode flag */ +extern int caml_gr_x, caml_gr_y; /* Coordinates of the current point */ +extern int caml_gr_color; /* Current *CAML* drawing color (can be -1) */ +extern XFontStruct * caml_gr_font; /* Current font */ +extern long caml_gr_selected_events; /* Events we are interested in */ -extern Bool direct_rgb; -extern int byte_order; -extern int bitmap_unit; -extern int bits_per_pixel; +extern Bool caml_gr_direct_rgb; +extern int caml_gr_byte_order; +extern int caml_gr_bitmap_unit; +extern int caml_gr_bits_per_pixel; -#define Wcvt(y) (grwindow.h - 1 - (y)) -#define Bcvt(y) (grbstore.h - 1 - (y)) -#define WtoB(y) ((y) + grbstore.h - grwindow.h) -#define BtoW(y) ((y) + grwindow.h - grbstore.h) +#define Wcvt(y) (caml_gr_window.h - 1 - (y)) +#define Bcvt(y) (caml_gr_bstore.h - 1 - (y)) +#define WtoB(y) ((y) + caml_gr_bstore.h - caml_gr_window.h) +#define BtoW(y) ((y) + caml_gr_window.h - caml_gr_bstore.h) #define min(a,b) ((a) < (b) ? (a) : (b)) #define max(a,b) ((a) > (b) ? (a) : (b)) @@ -74,11 +74,11 @@ extern int bits_per_pixel; #endif #endif -extern void gr_fail(char *fmt, char *arg); -extern void gr_check_open(void); -extern unsigned long gr_pixel_rgb(int rgb); -extern int gr_rgb_pixel(long unsigned int pixel); -extern void gr_handle_event(XEvent *e); -extern void gr_init_color_cache(void); -extern void gr_init_direct_rgb_to_pixel(void); -extern value id_of_window( Window w ); +extern void caml_gr_fail(char *fmt, char *arg); +extern void caml_gr_check_open(void); +extern unsigned long caml_gr_pixel_rgb(int rgb); +extern int caml_gr_rgb_pixel(long unsigned int pixel); +extern void caml_gr_handle_event(XEvent *e); +extern void caml_gr_init_color_cache(void); +extern void caml_gr_init_direct_rgb_to_pixel(void); +extern value caml_gr_id_of_window( Window w ); diff --git a/otherlibs/graph/make_img.c b/otherlibs/graph/make_img.c index a0d15a824..325e6698d 100644 --- a/otherlibs/graph/make_img.c +++ b/otherlibs/graph/make_img.c @@ -17,7 +17,7 @@ #include "image.h" #include <memory.h> -value gr_make_image(value m) +value caml_gr_make_image(value m) { int width, height; value im; @@ -28,20 +28,20 @@ value gr_make_image(value m) value line; GC gc; - gr_check_open(); + caml_gr_check_open(); height = Wosize_val(m); - if (height == 0) return gr_new_image(0, 0); + if (height == 0) return caml_gr_new_image(0, 0); width = Wosize_val(Field(m, 0)); for (i = 1; i < height; i++) if (Wosize_val(Field(m, i)) != width) - gr_fail("make_image: lines of different lengths", NULL); + caml_gr_fail("make_image: lines of different lengths", NULL); /* Build an XImage for the data part of the image */ idata = - XCreateImage(grdisplay, DefaultVisual(grdisplay, grscreen), - XDefaultDepth(grdisplay, grscreen), + XCreateImage(caml_gr_display, DefaultVisual(caml_gr_display, caml_gr_screen), + XDefaultDepth(caml_gr_display, caml_gr_screen), ZPixmap, 0, NULL, width, height, - BitmapPad(grdisplay), 0); + BitmapPad(caml_gr_display), 0); bdata = (char *) stat_alloc(height * idata->bytes_per_line); idata->data = bdata; @@ -52,7 +52,7 @@ value gr_make_image(value m) for (j = 0; j < width; j++) { rgb = Int_val(Field(line, j)); if (rgb == Transparent) { has_transp = True; rgb = 0; } - XPutPixel(idata, j, i, gr_pixel_rgb(rgb)); + XPutPixel(idata, j, i, caml_gr_pixel_rgb(rgb)); } } @@ -60,9 +60,9 @@ value gr_make_image(value m) build an XImage for the mask part of the image */ if (has_transp) { imask = - XCreateImage(grdisplay, DefaultVisual(grdisplay, grscreen), + XCreateImage(caml_gr_display, DefaultVisual(caml_gr_display, caml_gr_screen), 1, ZPixmap, 0, NULL, width, height, - BitmapPad(grdisplay), 0); + BitmapPad(caml_gr_display), 0); bmask = (char *) stat_alloc(height * imask->bytes_per_line); imask->data = bmask; @@ -78,18 +78,18 @@ value gr_make_image(value m) } /* Allocate the image and store the XImages into the Pixmaps */ - im = gr_new_image(width, height); - gc = XCreateGC(grdisplay, Data_im(im), 0, NULL); - XPutImage(grdisplay, Data_im(im), gc, idata, 0, 0, 0, 0, width, height); + im = caml_gr_new_image(width, height); + gc = XCreateGC(caml_gr_display, Data_im(im), 0, NULL); + XPutImage(caml_gr_display, Data_im(im), gc, idata, 0, 0, 0, 0, width, height); XDestroyImage(idata); - XFreeGC(grdisplay, gc); + XFreeGC(caml_gr_display, gc); if (has_transp) { - Mask_im(im) = XCreatePixmap(grdisplay, grwindow.win, width, height, 1); - gc = XCreateGC(grdisplay, Mask_im(im), 0, NULL); - XPutImage(grdisplay, Mask_im(im), gc, imask, 0, 0, 0, 0, width, height); + Mask_im(im) = XCreatePixmap(caml_gr_display, caml_gr_window.win, width, height, 1); + gc = XCreateGC(caml_gr_display, Mask_im(im), 0, NULL); + XPutImage(caml_gr_display, Mask_im(im), gc, imask, 0, 0, 0, 0, width, height); XDestroyImage(imask); - XFreeGC(grdisplay, gc); + XFreeGC(caml_gr_display, gc); } - XFlush(grdisplay); + XFlush(caml_gr_display); return im; } diff --git a/otherlibs/graph/open.c b/otherlibs/graph/open.c index e05eed591..2556cb17a 100644 --- a/otherlibs/graph/open.c +++ b/otherlibs/graph/open.c @@ -28,26 +28,26 @@ #include <sys/time.h> #endif -Display * grdisplay = NULL; -int grscreen; -Colormap grcolormap; -int grwhite, grblack, grbackground; -struct canvas grwindow; -struct canvas grbstore; -Bool grdisplay_mode; -Bool grremember_mode; -int grx, gry; -int grcolor; -extern XFontStruct * grfont; -long grselected_events; -static Bool gr_initialized = False; +Display * caml_gr_display = NULL; +int caml_gr_screen; +Colormap caml_gr_colormap; +int caml_gr_white, caml_gr_black, caml_gr_background; +struct canvas caml_gr_window; +struct canvas caml_gr_bstore; +Bool caml_gr_display_modeflag; +Bool caml_gr_remember_modeflag; +int caml_gr_x, caml_gr_y; +int caml_gr_color; +extern XFontStruct * caml_gr_font; +long caml_gr_selected_events; +static Bool caml_gr_initialized = False; static char * window_name = NULL; -static int gr_error_handler(Display *display, XErrorEvent *error); -static int gr_ioerror_handler(Display *display); -value gr_clear_graph(void); +static int caml_gr_error_handler(Display *display, XErrorEvent *error); +static int caml_gr_ioerror_handler(Display *display); +value caml_gr_clear_graph(void); -value gr_open_graph(value arg) +value caml_gr_open_graph(value arg) { char display_name[256], geometry_spec[64]; char * p, * q; @@ -57,8 +57,8 @@ value gr_open_graph(value arg) int x, y, w, h; XWindowAttributes attributes; - if (gr_initialized) { - gr_clear_graph(); + if (caml_gr_initialized) { + caml_gr_clear_graph(); } else { /* Parse the argument */ @@ -71,20 +71,20 @@ value gr_open_graph(value arg) *q = 0; /* Open the display */ - if (grdisplay == NULL) { - grdisplay = XOpenDisplay(display_name); - if (grdisplay == NULL) - gr_fail("Cannot open display %s", XDisplayName(display_name)); - grscreen = DefaultScreen(grdisplay); - grblack = BlackPixel(grdisplay, grscreen); - grwhite = WhitePixel(grdisplay, grscreen); - grbackground = grwhite; - grcolormap = DefaultColormap(grdisplay, grscreen); + if (caml_gr_display == NULL) { + caml_gr_display = XOpenDisplay(display_name); + if (caml_gr_display == NULL) + caml_gr_fail("Cannot open display %s", XDisplayName(display_name)); + caml_gr_screen = DefaultScreen(caml_gr_display); + caml_gr_black = BlackPixel(caml_gr_display, caml_gr_screen); + caml_gr_white = WhitePixel(caml_gr_display, caml_gr_screen); + caml_gr_background = caml_gr_white; + caml_gr_colormap = DefaultColormap(caml_gr_display, caml_gr_screen); } /* Set up the error handlers */ - XSetErrorHandler(gr_error_handler); - XSetIOErrorHandler(gr_ioerror_handler); + XSetErrorHandler(caml_gr_error_handler); + XSetIOErrorHandler(caml_gr_ioerror_handler); /* Parse the geometry specification */ hints.x = 0; @@ -94,7 +94,7 @@ value gr_open_graph(value arg) hints.flags = PPosition | PSize; hints.win_gravity = 0; - ret = XWMGeometry(grdisplay, grscreen, geometry_spec, "", BORDER_WIDTH, + ret = XWMGeometry(caml_gr_display, caml_gr_screen, geometry_spec, "", BORDER_WIDTH, &hints, &x, &y, &w, &h, &hints.win_gravity); if (ret & (XValue | YValue)) { hints.x = x; hints.y = y; hints.flags |= USPosition; @@ -104,59 +104,59 @@ value gr_open_graph(value arg) } /* Initial drawing color is black */ - grcolor = 0; /* CAML COLOR */ + caml_gr_color = 0; /* CAML COLOR */ /* Create the on-screen window */ - grwindow.w = hints.width; - grwindow.h = hints.height; - grwindow.win = - XCreateSimpleWindow(grdisplay, DefaultRootWindow(grdisplay), + caml_gr_window.w = hints.width; + caml_gr_window.h = hints.height; + caml_gr_window.win = + XCreateSimpleWindow(caml_gr_display, DefaultRootWindow(caml_gr_display), hints.x, hints.y, hints.width, hints.height, - BORDER_WIDTH, grblack, grbackground); + BORDER_WIDTH, caml_gr_black, caml_gr_background); p = window_name; if (p == NULL) p = DEFAULT_WINDOW_NAME; /* What not use XSetWMProperties? */ - XSetStandardProperties(grdisplay, grwindow.win, p, p, + XSetStandardProperties(caml_gr_display, caml_gr_window.win, p, p, None, NULL, 0, &hints); - grwindow.gc = XCreateGC(grdisplay, grwindow.win, 0, NULL); - XSetBackground(grdisplay, grwindow.gc, grbackground); - XSetForeground(grdisplay, grwindow.gc, grblack); + caml_gr_window.gc = XCreateGC(caml_gr_display, caml_gr_window.win, 0, NULL); + XSetBackground(caml_gr_display, caml_gr_window.gc, caml_gr_background); + XSetForeground(caml_gr_display, caml_gr_window.gc, caml_gr_black); /* Require exposure, resize and keyboard events */ - grselected_events = DEFAULT_SELECTED_EVENTS; - XSelectInput(grdisplay, grwindow.win, grselected_events); + caml_gr_selected_events = DEFAULT_SELECTED_EVENTS; + XSelectInput(caml_gr_display, caml_gr_window.win, caml_gr_selected_events); /* Map the window on the screen and wait for the first Expose event */ - XMapWindow(grdisplay, grwindow.win); - do { XNextEvent(grdisplay, &event); } while (event.type != Expose); + XMapWindow(caml_gr_display, caml_gr_window.win); + do { XNextEvent(caml_gr_display, &event); } while (event.type != Expose); /* Get the actual window dimensions */ - XGetWindowAttributes(grdisplay, grwindow.win, &attributes); - grwindow.w = attributes.width; - grwindow.h = attributes.height; + XGetWindowAttributes(caml_gr_display, caml_gr_window.win, &attributes); + caml_gr_window.w = attributes.width; + caml_gr_window.h = attributes.height; /* Create the pixmap used for backing store */ - grbstore.w = grwindow.w; - grbstore.h = grwindow.h; - grbstore.win = - XCreatePixmap(grdisplay, grwindow.win, grbstore.w, grbstore.h, - XDefaultDepth(grdisplay, grscreen)); - grbstore.gc = XCreateGC(grdisplay, grbstore.win, 0, NULL); - XSetBackground(grdisplay, grbstore.gc, grbackground); + caml_gr_bstore.w = caml_gr_window.w; + caml_gr_bstore.h = caml_gr_window.h; + caml_gr_bstore.win = + XCreatePixmap(caml_gr_display, caml_gr_window.win, caml_gr_bstore.w, caml_gr_bstore.h, + XDefaultDepth(caml_gr_display, caml_gr_screen)); + caml_gr_bstore.gc = XCreateGC(caml_gr_display, caml_gr_bstore.win, 0, NULL); + XSetBackground(caml_gr_display, caml_gr_bstore.gc, caml_gr_background); /* Clear the pixmap */ - XSetForeground(grdisplay, grbstore.gc, grbackground); - XFillRectangle(grdisplay, grbstore.win, grbstore.gc, - 0, 0, grbstore.w, grbstore.h); - XSetForeground(grdisplay, grbstore.gc, grblack); + XSetForeground(caml_gr_display, caml_gr_bstore.gc, caml_gr_background); + XFillRectangle(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, + 0, 0, caml_gr_bstore.w, caml_gr_bstore.h); + XSetForeground(caml_gr_display, caml_gr_bstore.gc, caml_gr_black); /* Set the display and remember modes on */ - grdisplay_mode = True ; - grremember_mode = True ; + caml_gr_display_modeflag = True ; + caml_gr_remember_modeflag = True ; /* The global data structures are now correctly initialized. - In particular, gr_sigio_handler can now handle events safely. */ - gr_initialized = True; + In particular, caml_gr_sigio_handler can now handle events safely. */ + caml_gr_initialized = True; /* If possible, request that system calls be restarted after the EVENT_SIGNAL signal. */ @@ -173,9 +173,9 @@ value gr_open_graph(value arg) #ifdef USE_ASYNC_IO /* If BSD-style asynchronous I/O are supported: arrange for I/O on the connection to trigger the SIGIO signal */ - ret = fcntl(ConnectionNumber(grdisplay), F_GETFL, 0); - fcntl(ConnectionNumber(grdisplay), F_SETFL, ret | FASYNC); - fcntl(ConnectionNumber(grdisplay), F_SETOWN, getpid()); + ret = fcntl(ConnectionNumber(caml_gr_display), F_GETFL, 0); + fcntl(ConnectionNumber(caml_gr_display), F_SETFL, ret | FASYNC); + fcntl(ConnectionNumber(caml_gr_display), F_SETOWN, getpid()); #endif } #ifdef USE_INTERVAL_TIMER @@ -194,35 +194,35 @@ value gr_open_graph(value arg) alarm(1); #endif /* Position the current point at origin */ - grx = 0; - gry = 0; + caml_gr_x = 0; + caml_gr_y = 0; /* Reset the color cache */ - gr_init_color_cache(); - gr_init_direct_rgb_to_pixel(); + caml_gr_init_color_cache(); + caml_gr_init_direct_rgb_to_pixel(); return Val_unit; } -value gr_close_graph(void) +value caml_gr_close_graph(void) { - if (gr_initialized) { + if (caml_gr_initialized) { #ifdef USE_INTERVAL_TIMER struct itimerval it; it.it_value.tv_sec = 0; it.it_value.tv_usec = 0; setitimer(ITIMER_REAL, &it, NULL); #endif - gr_initialized = False; - if (grfont != NULL) { XFreeFont(grdisplay, grfont); grfont = NULL; } - XFreeGC(grdisplay, grwindow.gc); - XDestroyWindow(grdisplay, grwindow.win); - XFreeGC(grdisplay, grbstore.gc); - XFreePixmap(grdisplay, grbstore.win); - XFlush(grdisplay); + caml_gr_initialized = False; + if (caml_gr_font != NULL) { XFreeFont(caml_gr_display, caml_gr_font); caml_gr_font = NULL; } + XFreeGC(caml_gr_display, caml_gr_window.gc); + XDestroyWindow(caml_gr_display, caml_gr_window.win); + XFreeGC(caml_gr_display, caml_gr_bstore.gc); + XFreePixmap(caml_gr_display, caml_gr_bstore.win); + XFlush(caml_gr_display); } return Val_unit; } -value id_of_window(Window win) +value caml_gr_id_of_window(Window win) { char tmp[256]; @@ -230,98 +230,98 @@ value id_of_window(Window win) return copy_string( tmp ); } -value gr_window_id(void) +value caml_gr_window_id(void) { - gr_check_open(); - return id_of_window(grwindow.win); + caml_gr_check_open(); + return caml_gr_id_of_window(caml_gr_window.win); } -value gr_set_window_title(value n) +value caml_gr_set_window_title(value n) { if (window_name != NULL) stat_free(window_name); window_name = stat_alloc(strlen(String_val(n))+1); strcpy(window_name, String_val(n)); - if (gr_initialized) { - XStoreName(grdisplay, grwindow.win, window_name); - XSetIconName(grdisplay, grwindow.win, window_name); - XFlush(grdisplay); + if (caml_gr_initialized) { + XStoreName(caml_gr_display, caml_gr_window.win, window_name); + XSetIconName(caml_gr_display, caml_gr_window.win, window_name); + XFlush(caml_gr_display); } return Val_unit; } -value gr_clear_graph(void) +value caml_gr_clear_graph(void) { - gr_check_open(); - if(grremember_mode) { - XSetForeground(grdisplay, grbstore.gc, grwhite); - XFillRectangle(grdisplay, grbstore.win, grbstore.gc, - 0, 0, grbstore.w, grbstore.h); - XSetForeground(grdisplay, grbstore.gc, grcolor); + caml_gr_check_open(); + if(caml_gr_remember_modeflag) { + XSetForeground(caml_gr_display, caml_gr_bstore.gc, caml_gr_white); + XFillRectangle(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, + 0, 0, caml_gr_bstore.w, caml_gr_bstore.h); + XSetForeground(caml_gr_display, caml_gr_bstore.gc, caml_gr_color); } - if(grdisplay_mode) { - XSetForeground(grdisplay, grwindow.gc, grwhite); - XFillRectangle(grdisplay, grwindow.win, grwindow.gc, - 0, 0, grwindow.w, grwindow.h); - XSetForeground(grdisplay, grwindow.gc, grcolor); - XFlush(grdisplay); + if(caml_gr_display_modeflag) { + XSetForeground(caml_gr_display, caml_gr_window.gc, caml_gr_white); + XFillRectangle(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, + 0, 0, caml_gr_window.w, caml_gr_window.h); + XSetForeground(caml_gr_display, caml_gr_window.gc, caml_gr_color); + XFlush(caml_gr_display); } - gr_init_color_cache(); - gr_init_direct_rgb_to_pixel(); + caml_gr_init_color_cache(); + caml_gr_init_direct_rgb_to_pixel(); return Val_unit; } -value gr_size_x(void) +value caml_gr_size_x(void) { - gr_check_open(); - return Val_int(grwindow.w); + caml_gr_check_open(); + return Val_int(caml_gr_window.w); } -value gr_size_y(void) +value caml_gr_size_y(void) { - gr_check_open(); - return Val_int(grwindow.h); + caml_gr_check_open(); + return Val_int(caml_gr_window.h); } -value gr_synchronize(void) +value caml_gr_synchronize(void) { - gr_check_open(); - XCopyArea(grdisplay, grbstore.win, grwindow.win, grwindow.gc, - 0, grbstore.h - grwindow.h, - grwindow.w, grwindow.h, + caml_gr_check_open(); + XCopyArea(caml_gr_display, caml_gr_bstore.win, caml_gr_window.win, caml_gr_window.gc, + 0, caml_gr_bstore.h - caml_gr_window.h, + caml_gr_window.w, caml_gr_window.h, 0, 0); - XFlush(grdisplay); + XFlush(caml_gr_display); return Val_unit ; } -value gr_display_mode(value flag) +value caml_gr_display_mode(value flag) { - grdisplay_mode = Bool_val (flag); + caml_gr_display_modeflag = Bool_val (flag); return Val_unit ; } -value gr_remember_mode(value flag) +value caml_gr_remember_mode(value flag) { - grremember_mode = Bool_val(flag); + caml_gr_remember_modeflag = Bool_val(flag); return Val_unit ; } -/* The gr_sigio_handler is called via the signal machinery in the bytecode +/* The caml_gr_sigio_handler is called via the signal machinery in the bytecode interpreter. The signal system ensures that this function will be called either between two bytecode instructions, or during a blocking primitive. In either case, not in the middle of an Xlib call. */ -value gr_sigio_signal(value unit) +value caml_gr_sigio_signal(value unit) { return Val_int(EVENT_SIGNAL); } -value gr_sigio_handler(void) +value caml_gr_sigio_handler(void) { XEvent grevent; - if (gr_initialized) { - while (XCheckMaskEvent(grdisplay, -1 /*all events*/, &grevent)) { - gr_handle_event(&grevent); + if (caml_gr_initialized) { + while (XCheckMaskEvent(caml_gr_display, -1 /*all events*/, &grevent)) { + caml_gr_handle_event(&grevent); } } #ifdef USE_ALARM @@ -334,7 +334,7 @@ value gr_sigio_handler(void) static value * graphic_failure_exn = NULL; -void gr_fail(char *fmt, char *arg) +void caml_gr_fail(char *fmt, char *arg) { char buffer[1024]; @@ -347,21 +347,21 @@ void gr_fail(char *fmt, char *arg) raise_with_string(*graphic_failure_exn, buffer); } -void gr_check_open(void) +void caml_gr_check_open(void) { - if (!gr_initialized) gr_fail("graphic screen not opened", NULL); + if (!caml_gr_initialized) caml_gr_fail("graphic screen not opened", NULL); } -static int gr_error_handler(Display *display, XErrorEvent *error) +static int caml_gr_error_handler(Display *display, XErrorEvent *error) { char errmsg[512]; XGetErrorText(error->display, error->error_code, errmsg, sizeof(errmsg)); - gr_fail("Xlib error: %s", errmsg); + caml_gr_fail("Xlib error: %s", errmsg); return 0; } -static int gr_ioerror_handler(Display *display) +static int caml_gr_ioerror_handler(Display *display) { - gr_fail("fatal I/O error", NULL); + caml_gr_fail("fatal I/O error", NULL); return 0; } diff --git a/otherlibs/graph/point_col.c b/otherlibs/graph/point_col.c index 8df0dfaf0..ffcdc2100 100644 --- a/otherlibs/graph/point_col.c +++ b/otherlibs/graph/point_col.c @@ -15,16 +15,16 @@ #include "libgraph.h" -value gr_point_color(value vx, value vy) +value caml_gr_point_color(value vx, value vy) { int x = Int_val(vx); int y = Int_val(vy); XImage * im; int rgb; - gr_check_open(); - im = XGetImage(grdisplay, grbstore.win, x, Bcvt(y), 1, 1, (-1), ZPixmap); - rgb = gr_rgb_pixel(XGetPixel(im, 0, 0)); + caml_gr_check_open(); + im = XGetImage(caml_gr_display, caml_gr_bstore.win, x, Bcvt(y), 1, 1, (-1), ZPixmap); + rgb = caml_gr_rgb_pixel(XGetPixel(im, 0, 0)); XDestroyImage(im); return Val_int(rgb); } diff --git a/otherlibs/graph/sound.c b/otherlibs/graph/sound.c index 4b3062206..dc75b7ed0 100644 --- a/otherlibs/graph/sound.c +++ b/otherlibs/graph/sound.c @@ -15,20 +15,20 @@ #include "libgraph.h" -value gr_sound(value vfreq, value vdur) +value caml_gr_sound(value vfreq, value vdur) { XKeyboardControl kbdcontrol; - gr_check_open(); + caml_gr_check_open(); kbdcontrol.bell_pitch = Int_val(vfreq); kbdcontrol.bell_duration = Int_val(vdur); - XChangeKeyboardControl(grdisplay, KBBellPitch | KBBellDuration, + XChangeKeyboardControl(caml_gr_display, KBBellPitch | KBBellDuration, &kbdcontrol); - XBell(grdisplay, 0); + XBell(caml_gr_display, 0); kbdcontrol.bell_pitch = -1; /* restore default value */ kbdcontrol.bell_duration = -1; /* restore default value */ - XChangeKeyboardControl(grdisplay, KBBellPitch | KBBellDuration, + XChangeKeyboardControl(caml_gr_display, KBBellPitch | KBBellDuration, &kbdcontrol); - XFlush(grdisplay); + XFlush(caml_gr_display); return Val_unit; } diff --git a/otherlibs/graph/subwindow.c b/otherlibs/graph/subwindow.c index a97242de0..642e28c40 100644 --- a/otherlibs/graph/subwindow.c +++ b/otherlibs/graph/subwindow.c @@ -15,7 +15,7 @@ #include "libgraph.h" -value gr_open_subwindow(value vx, value vy, value width, value height) +value caml_gr_open_subwindow(value vx, value vy, value width, value height) { Window win; @@ -24,22 +24,22 @@ value gr_open_subwindow(value vx, value vy, value width, value height) int x = Int_val(vx); int y = Int_val(vy); - gr_check_open(); - win = XCreateSimpleWindow(grdisplay, grwindow.win, + caml_gr_check_open(); + win = XCreateSimpleWindow(caml_gr_display, caml_gr_window.win, x, Wcvt(y + h), w, h, - 0, grblack, grbackground); - XMapWindow(grdisplay, win); - XFlush(grdisplay); - return (id_of_window (win)); + 0, caml_gr_black, caml_gr_background); + XMapWindow(caml_gr_display, win); + XFlush(caml_gr_display); + return (caml_gr_id_of_window (win)); } -value gr_close_subwindow(value wid) +value caml_gr_close_subwindow(value wid) { Window win; - gr_check_open(); + caml_gr_check_open(); sscanf( String_val(wid), "%lu", (unsigned long *)(&win) ); - XDestroyWindow(grdisplay, win); - XFlush(grdisplay); + XDestroyWindow(caml_gr_display, win); + XFlush(caml_gr_display); return Val_unit; } diff --git a/otherlibs/graph/text.c b/otherlibs/graph/text.c index ad41f2ff2..f4d980aed 100644 --- a/otherlibs/graph/text.c +++ b/otherlibs/graph/text.c @@ -16,69 +16,69 @@ #include "libgraph.h" #include <alloc.h> -XFontStruct * grfont = NULL; +XFontStruct * caml_gr_font = NULL; -static void gr_font(char *fontname) +static void caml_gr_get_font(char *fontname) { - XFontStruct * font = XLoadQueryFont(grdisplay, fontname); - if (font == NULL) gr_fail("cannot find font %s", fontname); - if (grfont != NULL) XFreeFont(grdisplay, grfont); - grfont = font; - XSetFont(grdisplay, grwindow.gc, grfont->fid); - XSetFont(grdisplay, grbstore.gc, grfont->fid); + XFontStruct * font = XLoadQueryFont(caml_gr_display, fontname); + if (font == NULL) caml_gr_fail("cannot find font %s", fontname); + if (caml_gr_font != NULL) XFreeFont(caml_gr_display, caml_gr_font); + caml_gr_font = font; + XSetFont(caml_gr_display, caml_gr_window.gc, caml_gr_font->fid); + XSetFont(caml_gr_display, caml_gr_bstore.gc, caml_gr_font->fid); } -value gr_set_font(value fontname) +value caml_gr_set_font(value fontname) { - gr_check_open(); - gr_font(String_val(fontname)); + caml_gr_check_open(); + caml_gr_get_font(String_val(fontname)); return Val_unit; } -value gr_set_text_size (value sz) +value caml_gr_set_text_size (value sz) { return Val_unit; } -static void gr_draw_text(char *txt, int len) +static void caml_gr_draw_text(char *txt, int len) { - if (grfont == NULL) gr_font(DEFAULT_FONT); - if (grremember_mode) - XDrawString(grdisplay, grbstore.win, grbstore.gc, - grx, Bcvt(gry) - grfont->descent + 1, txt, len); - if (grdisplay_mode) { - XDrawString(grdisplay, grwindow.win, grwindow.gc, - grx, Wcvt(gry) - grfont->descent + 1, txt, len); - XFlush(grdisplay); + if (caml_gr_font == NULL) caml_gr_get_font(DEFAULT_FONT); + if (caml_gr_remember_modeflag) + XDrawString(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, + caml_gr_x, Bcvt(caml_gr_y) - caml_gr_font->descent + 1, txt, len); + if (caml_gr_display_modeflag) { + XDrawString(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, + caml_gr_x, Wcvt(caml_gr_y) - caml_gr_font->descent + 1, txt, len); + XFlush(caml_gr_display); } - grx += XTextWidth(grfont, txt, len); + caml_gr_x += XTextWidth(caml_gr_font, txt, len); } -value gr_draw_char(value chr) +value caml_gr_draw_char(value chr) { char str[1]; - gr_check_open(); + caml_gr_check_open(); str[0] = Int_val(chr); - gr_draw_text(str, 1); + caml_gr_draw_text(str, 1); return Val_unit; } -value gr_draw_string(value str) +value caml_gr_draw_string(value str) { - gr_check_open(); - gr_draw_text(String_val(str), string_length(str)); + caml_gr_check_open(); + caml_gr_draw_text(String_val(str), string_length(str)); return Val_unit; } -value gr_text_size(value str) +value caml_gr_text_size(value str) { int width; value res; - gr_check_open(); - if (grfont == NULL) gr_font(DEFAULT_FONT); - width = XTextWidth(grfont, String_val(str), string_length(str)); + caml_gr_check_open(); + if (caml_gr_font == NULL) caml_gr_get_font(DEFAULT_FONT); + width = XTextWidth(caml_gr_font, String_val(str), string_length(str)); res = alloc_small(2, 0); Field(res, 0) = Val_int(width); - Field(res, 1) = Val_int(grfont->ascent + grfont->descent); + Field(res, 1) = Val_int(caml_gr_font->ascent + caml_gr_font->descent); return res; } |