1 /**************************************************************************/
2 /*                                                                        */
3 /*                                 OCaml                                  */
4 /*                                                                        */
5 /*             Xavier Leroy, projet Cristal, INRIA Rocquencourt           */
6 /*                                                                        */
7 /*   Copyright 1996 Institut National de Recherche en Informatique et     */
8 /*     en Automatique.                                                    */
9 /*                                                                        */
10 /*   All rights reserved.  This file is distributed under the terms of    */
11 /*   the GNU Lesser General Public License version 2.1, with the          */
12 /*   special exception on linking described in the file LICENSE.          */
13 /*                                                                        */
14 /**************************************************************************/
15 
16 #include "libgraph.h"
17 #include <caml/memory.h>
18 
caml_gr_fill_rect(value vx,value vy,value vw,value vh)19 value caml_gr_fill_rect(value vx, value vy, value vw, value vh)
20 {
21   int x = Int_val(vx);
22   int y = Int_val(vy);
23   int w = Int_val(vw);
24   int h = Int_val(vh);
25 
26   caml_gr_check_open();
27   if(caml_gr_remember_modeflag)
28     XFillRectangle(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc,
29                    x, Bcvt(y) - h, w + 1, h + 1);
30   if(caml_gr_display_modeflag) {
31     XFillRectangle(caml_gr_display, caml_gr_window.win, caml_gr_window.gc,
32            x, Wcvt(y) - h, w + 1, h + 1);
33     XFlush(caml_gr_display);
34   }
35   return Val_unit;
36 }
37 
caml_gr_fill_poly(value array)38 value caml_gr_fill_poly(value array)
39 {
40   XPoint * points;
41   int npoints, i;
42 
43   caml_gr_check_open();
44   npoints = Wosize_val(array);
45   points = (XPoint *) caml_stat_alloc(npoints * sizeof(XPoint));
46   for (i = 0; i < npoints; i++) {
47     points[i].x = Int_val(Field(Field(array, i), 0));
48     points[i].y = Bcvt(Int_val(Field(Field(array, i), 1)));
49   }
50   if(caml_gr_remember_modeflag)
51     XFillPolygon(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc, points,
52                  npoints, Complex, CoordModeOrigin);
53   if(caml_gr_display_modeflag) {
54     for (i = 0; i < npoints; i++)
55       points[i].y = BtoW(points[i].y);
56     XFillPolygon(caml_gr_display, caml_gr_window.win, caml_gr_window.gc, points,
57          npoints, Complex, CoordModeOrigin);
58     XFlush(caml_gr_display);
59   }
60   caml_stat_free((char *) points);
61   return Val_unit;
62 }
63 
caml_gr_fill_arc_nat(value vx,value vy,value vrx,value vry,value va1,value va2)64 value caml_gr_fill_arc_nat(value vx, value vy, value vrx, value vry, value va1,
65                            value va2)
66 {
67   int x = Int_val(vx);
68   int y = Int_val(vy);
69   int rx = Int_val(vrx);
70   int ry = Int_val(vry);
71   int a1 = Int_val(va1);
72   int a2 = Int_val(va2);
73 
74   caml_gr_check_open();
75   if(caml_gr_remember_modeflag)
76     XFillArc(caml_gr_display, caml_gr_bstore.win, caml_gr_bstore.gc,
77              x - rx, Bcvt(y) - ry, rx * 2, ry * 2, a1 * 64, (a2 - a1) * 64);
78   if(caml_gr_display_modeflag) {
79     XFillArc(caml_gr_display, caml_gr_window.win, caml_gr_window.gc,
80          x - rx, Wcvt(y) - ry, rx * 2, ry * 2, a1 * 64, (a2 - a1) * 64);
81     XFlush(caml_gr_display);
82   }
83   return Val_unit;
84 }
85 
caml_gr_fill_arc(value * argv,int argc)86 value caml_gr_fill_arc(value *argv, int argc)
87 {
88   return caml_gr_fill_arc_nat(argv[0], argv[1], argv[2], argv[3], argv[4],
89                               argv[5]);
90 }
91