~uhh-ssd/+junk/humidity_readout

« back to all changes in this revision

Viewing changes to plplot/plplot-5.9.9/bindings/ocaml/plplot_core.idl

  • Committer: Joachim Erfle
  • Date: 2013-07-24 13:53:41 UTC
  • Revision ID: joachim.erfle@desy.de-20130724135341-1qojpp701zsn009p
initial commit

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
/*
 
2
Copyright 2007, 2008, 2009, 2010, 2011  Hezekiah M. Carty
 
3
 
 
4
This file is part of ocaml-plplot.
 
5
 
 
6
ocaml-plplot is free software: you can redistribute it and/or modify
 
7
it under the terms of the GNU Lesser General Public License as published by
 
8
the Free Software Foundation, either version 2 of the License, or
 
9
(at your option) any later version.
 
10
 
 
11
Foobar is distributed in the hope that it will be useful,
 
12
but WITHOUT ANY WARRANTY; without even the implied warranty of
 
13
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
 
14
GNU Lesser General Public License for more details.
 
15
 
 
16
You should have received a copy of the GNU Lesser General Public License
 
17
along with ocaml-plplot.  If not, see <http://www.gnu.org/licenses/>.
 
18
*/
 
19
 
 
20
// Taken from the plplot.h 3D plot style definitions
 
21
enum plplot3d_style_enum {
 
22
    PL_DIFFUSE = 0,
 
23
    PL_DRAW_LINEX = 1,
 
24
    PL_DRAW_LINEY = 2,
 
25
    PL_DRAW_LINEXY = 3,
 
26
    PL_MAG_COLOR = 4,
 
27
    PL_BASE_CONT = 8,
 
28
    PL_TOP_CONT = 16,
 
29
    PL_SURF_CONT = 32,
 
30
    PL_DRAW_SIDES = 64,
 
31
    PL_FACETED = 128,
 
32
    PL_MESH = 256
 
33
};
 
34
typedef [set] enum plplot3d_style_enum plplot3d_style;
 
35
 
 
36
enum plplot_bin_enum {
 
37
    PL_BIN_DEFAULT = 0,
 
38
    PL_BIN_CENTRED = 1,
 
39
    PL_BIN_NOEXPAND = 2,
 
40
    PL_BIN_NOEMPTY = 4,
 
41
};
 
42
typedef [set] enum plplot_bin_enum plplot_bin_style;
 
43
 
 
44
enum plplot_hist_enum {
 
45
    PL_HIST_DEFAULT = 0,
 
46
    PL_HIST_NOSCALING = 1,
 
47
    PL_HIST_IGNORE_OUTLIERS = 2,
 
48
    PL_HIST_NOEXPAND = 8,
 
49
    PL_HIST_NOEMPTY = 16,
 
50
};
 
51
typedef [set] enum plplot_hist_enum plplot_hist_style;
 
52
 
 
53
enum plplot_run_level_enum {
 
54
    PL_UNINITIALIZED = 0,
 
55
    PL_INITIALIZED = 1,
 
56
    PL_VIEWPORT_DEFINED = 2,
 
57
    PL_WORLD_COORDINATES_DEFINED = 3,
 
58
};
 
59
typedef enum plplot_run_level_enum plplot_run_level;
 
60
 
 
61
enum plplot_position_enum {
 
62
    PL_POSITION_LEFT = 0x1,
 
63
    PL_POSITION_RIGHT = 0x2,
 
64
    PL_POSITION_TOP = 0x4,
 
65
    PL_POSITION_BOTTOM = 0x8,
 
66
    PL_POSITION_INSIDE = 0x10,
 
67
    PL_POSITION_OUTSIDE = 0x20,
 
68
    PL_POSITION_VIEWPORT = 0x40,
 
69
    PL_POSITION_SUBPAGE = 0x80,
 
70
};
 
71
typedef [set] enum plplot_position_enum plplot_position_opt;
 
72
 
 
73
enum plplot_legend_enum {
 
74
    PL_LEGEND_NONE = 0x1,
 
75
    PL_LEGEND_COLOR_BOX = 0x2,
 
76
    PL_LEGEND_LINE = 0x4,
 
77
    PL_LEGEND_SYMBOL = 0x8,
 
78
    PL_LEGEND_TEXT_LEFT = 0x10,
 
79
    PL_LEGEND_BACKGROUND = 0x20,
 
80
    PL_LEGEND_BOUNDING_BOX = 0x40,
 
81
    PL_LEGEND_ROW_MAJOR = 0x80,
 
82
};
 
83
typedef [set] enum plplot_legend_enum plplot_legend_opt;
 
84
 
 
85
enum plplot_colorbar_enum {
 
86
    PL_COLORBAR_LABEL_LEFT = 0x1,
 
87
    PL_COLORBAR_LABEL_RIGHT = 0x2,
 
88
    PL_COLORBAR_LABEL_TOP = 0x4,
 
89
    PL_COLORBAR_LABEL_BOTTOM = 0x8,
 
90
    PL_COLORBAR_IMAGE = 0x10,
 
91
    PL_COLORBAR_SHADE = 0x20,
 
92
    PL_COLORBAR_GRADIENT = 0x40,
 
93
    PL_COLORBAR_CAP_NONE = 0x80,
 
94
    PL_COLORBAR_CAP_LOW = 0x100,
 
95
    PL_COLORBAR_CAP_HIGH = 0x200,
 
96
    PL_COLORBAR_SHADE_LABEL = 0x400,
 
97
    PL_COLORBAR_ORIENT_RIGHT = 0x800,
 
98
    PL_COLORBAR_ORIENT_TOP = 0x1000,
 
99
    PL_COLORBAR_ORIENT_LEFT = 0x2000,
 
100
    PL_COLORBAR_ORIENT_BOTTOM = 0x4000,
 
101
    PL_COLORBAR_BACKGROUND = 0x8000,
 
102
    PL_COLORBAR_BOUNDING_BOX = 0x10000,
 
103
};
 
104
typedef [set] enum plplot_colorbar_enum plplot_colorbar_opt;
 
105
 
 
106
enum plplot_fci_family_enum {
 
107
    // = These are legal values for font family attribute
 
108
    PL_FCI_FAMILY_UNCHANGED = -1,
 
109
    PL_FCI_SANS = 0x0,
 
110
    PL_FCI_SERIF = 0x1,
 
111
    PL_FCI_MONO = 0x2,
 
112
    PL_FCI_SCRIPT = 0x3,
 
113
    PL_FCI_SYMBOL = 0x4
 
114
};
 
115
enum plplot_fci_style_enum {
 
116
    // = These are legal values for font style attribute
 
117
    PL_FCI_STYLE_UNCHANGED = -1,
 
118
    PL_FCI_UPRIGHT = 0x0,
 
119
    PL_FCI_ITALIC = 0x1,
 
120
    PL_FCI_OBLIQUE = 0x2
 
121
};
 
122
enum plplot_fci_weight_enum {
 
123
    // = These are legal values for font weight attribute
 
124
    PL_FCI_WEIGHT_UNCHANGED = -1,
 
125
    PL_FCI_MEDIUM = 0x0,
 
126
    PL_FCI_BOLD = 0x1
 
127
};
 
128
 
 
129
enum plplot_draw_mode_enum {
 
130
    // Flags for drawing mode
 
131
    PL_DRAWMODE_UNKNOWN = 0x0,
 
132
    PL_DRAWMODE_DEFAULT = 0x1,
 
133
    PL_DRAWMODE_REPLACE = 0x2,
 
134
    PL_DRAWMODE_XOR = 0x4
 
135
};
 
136
 
 
137
// Any function which has a nonzero_error_int return type will raise
 
138
// an Invalid_argument error if the return value is <> 0.
 
139
typedef [errorcheck(plplot_check_nonzero_result), errorcode] int nonzero_error_int;
 
140
 
 
141
// Include the prototype for this to avoid implicit declaration warnings
 
142
quote(h, "void plplot_check_nonzero_result(int result);");
 
143
 
 
144
// This is a simplified and modified version of the plplot.h file.
 
145
#include "plplot_h.inc"
 
146
 
 
147
// These functions require(d) some manual assistance to get them to work
 
148
// properly
 
149
#define PLINT int
 
150
#define PLFLT double
 
151
#define PLBOOL boolean
 
152
 
 
153
[mlname(plcont)] void ml_plcont(
 
154
    [size_is(nx,ny)] PLFLT **f, PLINT nx, PLINT ny,
 
155
    PLINT kx, PLINT lx, PLINT ky, PLINT ly,
 
156
    [size_is(nlevel)] PLFLT *clevel, PLINT nlevel);
 
157
 
 
158
[mlname(plshade)] void ml_plshade(
 
159
    [size_is(nx,ny)] PLFLT **a, PLINT nx, PLINT ny,
 
160
    PLFLT left, PLFLT right, PLFLT bottom, PLFLT top,
 
161
    PLFLT shade_min, PLFLT shade_max,
 
162
    PLINT sh_cmap, PLFLT sh_color, PLINT sh_width,
 
163
    PLINT min_color, PLINT min_width,
 
164
    PLINT max_color, PLINT max_width,
 
165
    PLBOOL rectangular);
 
166
 
 
167
[mlname(plshades)] void ml_plshades(
 
168
    [size_is(nx,ny)] PLFLT **a, PLINT nx, PLINT ny,
 
169
    PLFLT xmin, PLFLT xmax, PLFLT ymin, PLFLT ymax,
 
170
    [size_is(nlevel)] PLFLT *clevel, PLINT nlevel, PLINT fill_width,
 
171
    PLINT cont_color, PLINT cont_width,
 
172
    PLBOOL rectangular);
 
173
 
 
174
[mlname(plimagefr)] void ml_plimagefr(
 
175
    [size_is(nx, ny)] PLFLT **idata, PLINT nx, PLINT ny,
 
176
    PLFLT xmin, PLFLT xmax, PLFLT ymin, PLFLT ymax,
 
177
    PLFLT zmin, PLFLT zmax,
 
178
    PLFLT valuemin, PLFLT valuemax);
 
179
 
 
180
[mlname(plvect)] void ml_plvect(
 
181
    [size_is(nx,ny)] PLFLT **u, [size_is(nx,ny)] PLFLT **v,
 
182
    PLINT nx, PLINT ny, PLFLT scale);
 
183
 
 
184
[mlname(plmap)] void ml_plmap(
 
185
    [string] const char *type,
 
186
    PLFLT minlong, PLFLT maxlong, PLFLT minlat, PLFLT maxlat);
 
187
 
 
188
[mlname(plmeridians)] void ml_plmeridians(
 
189
    PLFLT dlong, PLFLT dlat,
 
190
    PLFLT minlong, PLFLT maxlong, PLFLT minlat, PLFLT maxlat);
 
191
 
 
192
[mlname(plpoly3)] void ml_plpoly3(
 
193
    PLINT n, [size_is(n)] PLFLT *x, [size_is(n)] PLFLT *y, [size_is(n)] PLFLT *z,
 
194
    PLINT ndraw, [size_is(ndraw)] PLBOOL *draw, PLBOOL ifcc);
 
195
 
 
196
// The following are for the pltr functions
 
197
[mlname(pltr0)] void ml_pltr0(
 
198
    PLFLT x, PLFLT y, [out] PLFLT *tx, [out] PLFLT *ty);
 
199
 
 
200
// XXX The following are non-standard functions which help retrieve some extra
 
201
// information from PLplot.
 
202
int plg_current_col0(void);
 
203
float plg_current_col1(void);
 
204
int plgwid(void);
 
205
float plgchrht(void);
 
206
 
 
207
#define QUOTEME(x) #x
 
208
#define RAW_ML(x) quote(mlmli, QUOTEME(x));
 
209
 
 
210
// plstripc function
 
211
quote(mlmli,
 
212
    "external plstripc : string -> string -> float -> float -> float -> float -> \
 
213
                         float -> float -> float -> bool -> bool -> int -> int -> \
 
214
                         int array -> int array -> string array -> string -> \
 
215
                         string -> string -> int = \"ml_plstripc_byte\" \"ml_plstripc\"");
 
216
 
 
217
// pltr callback functions, hand-wrapped
 
218
quote(mlmli,
 
219
    "external pltr1 : float array -> float array -> float -> float -> float * float \
 
220
    = \"ml_pltr1\"");
 
221
quote(mlmli,
 
222
    "external pltr2 : float array array -> float array array -> float -> float -> float * float \
 
223
    = \"ml_pltr2\"");
 
224
 
 
225
// Setting the translation function for the contouring and plotting functions
 
226
quote(ml,
 
227
    "let plset_pltr (f : float -> float -> (float * float)) =\
 
228
     Callback.register \"caml_plplot_plotter\" f");
 
229
quote(mli, "val plset_pltr : (float -> float -> (float * float)) -> unit");
 
230
quote(ml, "let plunset_pltr () = Callback.register \"caml_plplot_plotter\" 0");
 
231
quote(mli, "val plunset_pltr : unit -> unit");
 
232
 
 
233
// Setting the translation function for the map drawing functions
 
234
quote(ml,
 
235
    "let plset_mapform (f : float -> float -> (float * float)) =\
 
236
     Callback.register \"caml_plplot_mapform\" f");
 
237
quote(mli, "val plset_mapform : (float -> float -> (float * float)) -> unit");
 
238
quote(ml,
 
239
    "let plunset_mapform () = Callback.register \"caml_plplot_mapform\" 0");
 
240
quote(mli, "val plunset_mapform : unit -> unit");
 
241
 
 
242
// Setting the "defined" function for the shading functions
 
243
quote(ml,
 
244
"let plset_defined (f : float -> float -> int) =\
 
245
  Callback.register \"caml_plplot_defined\" f");
 
246
quote(mli, "val plset_defined : (float -> float -> int) -> unit");
 
247
quote(ml,
 
248
    "let plunset_defined () = Callback.register \"caml_plplot_defined\" 0");
 
249
quote(mli, "val plunset_defined : unit -> unit");
 
250
 
 
251
// Setting the translation function for the global coordinate transform
 
252
quote(ml, "external ml_plstransform : unit -> unit = \"ml_plstransform\"");
 
253
quote(ml,
 
254
    "let plstransform (f : float -> float -> (float * float)) =\
 
255
     Callback.register \"caml_plplot_transform\" f;\
 
256
     ml_plstransform ()");
 
257
quote(mli, "val plstransform : (float -> float -> (float * float)) -> unit");
 
258
quote(ml,
 
259
    "let plunset_transform () =\
 
260
    Callback.register \"caml_plplot_transform\" 0;\
 
261
    ml_plstransform ()");
 
262
quote(mli, "val plunset_transform : unit -> unit");
 
263
 
 
264
// Hand-translated PL_GRID_* flags for use with plgriddata
 
265
quote(mlmli, "type plplot_grid_method_type = \
 
266
                PL_GRID_CSA | \
 
267
                PL_GRID_DTLI | \
 
268
                PL_GRID_NNI | \
 
269
                PL_GRID_NNIDW | \
 
270
                PL_GRID_NNLI | \
 
271
                PL_GRID_NNAIDW");
 
272
 
 
273
// Hand-translated PL_PARSE_* flags for use with plparseopts
 
274
quote(mlmli, "type plplot_parse_method_type = \
 
275
                PL_PARSE_PARTIAL | \
 
276
                PL_PARSE_FULL | \
 
277
                PL_PARSE_QUIET | \
 
278
                PL_PARSE_NODELETE | \
 
279
                PL_PARSE_SHOWALL | \
 
280
                PL_PARSE_OVERRIDE | \
 
281
                PL_PARSE_NOPROGRAM | \
 
282
                PL_PARSE_NODASH | \
 
283
                PL_PARSE_SKIP");
 
284
 
 
285
// Data type to reference axes
 
286
quote(mlmli, "type plplot_axis_type = \
 
287
                PL_X_AXIS | \
 
288
                PL_Y_AXIS | \
 
289
                PL_Z_AXIS");
 
290
 
 
291
// Custom axis labeling
 
292
quote(ml, "external ml_plslabelfunc : unit -> unit = \"ml_plslabelfunc\"");
 
293
quote(ml,
 
294
"let plslabelfunc (f : plplot_axis_type -> float -> string) =\
 
295
  Callback.register \"caml_plplot_customlabel\" f;\
 
296
  ml_plslabelfunc ()");
 
297
quote(mli, "val plslabelfunc : (plplot_axis_type -> float -> string) -> unit");
 
298
quote(ml,
 
299
"let plunset_labelfunc () =\
 
300
  Callback.register \"caml_plplot_customlabel\" 0;\
 
301
  ml_plslabelfunc ()");
 
302
quote(mli, "val plunset_labelfunc : unit -> unit");
 
303
 
 
304
// Custom plabort handling
 
305
quote(ml, "external ml_plsabort : unit -> unit = \"ml_plsabort\"");
 
306
quote(ml,
 
307
"let plsabort (f : string -> unit) =\
 
308
  Callback.register \"caml_plplot_abort\" f;\
 
309
  ml_plsabort ()");
 
310
quote(mli, "val plsabort : (string -> unit) -> unit");
 
311
quote(ml,
 
312
"let plunset_abort () =\
 
313
  Callback.register \"caml_plplot_abort\" 0;\
 
314
  ml_plsabort ()");
 
315
quote(mli, "val plunset_abort : unit -> unit");
 
316
 
 
317
// Custom plexit handling
 
318
quote(ml, "external ml_plsexit : unit -> unit = \"ml_plsexit\"");
 
319
quote(ml,
 
320
"let plsexit (f : string -> int) =\
 
321
  Callback.register \"caml_plplot_exit\" f;\
 
322
  ml_plsexit ()");
 
323
quote(mli, "val plsexit : (string -> int) -> unit");
 
324
quote(ml,
 
325
"let plunset_exit () =\
 
326
  Callback.register \"caml_plplot_exit\" 0;\
 
327
  ml_plsexit ()");
 
328
quote(mli, "val plunset_exit : unit -> unit");
 
329
 
 
330
RAW_ML(external plgriddata : float array -> float array -> float array -> float array -> float array -> plplot_grid_method_type -> float -> float array array = "ml_plgriddata_bytecode" "ml_plgriddata")
 
331
RAW_ML(external plparseopts : string array -> plplot_parse_method_type list -> unit = "ml_plparseopts")
 
332
RAW_ML(external pllegend : plplot_legend_opt -> plplot_position_opt -> float -> float -> float -> int -> int -> int -> int -> int -> plplot_legend_opt array -> float -> float -> float -> float -> int array -> string array -> int array -> int array -> float array -> int array -> int array -> int array -> int array -> int array -> float array -> int array -> string array -> float * float = "ml_pllegend_byte" "ml_pllegend")
 
333