1(*
2        plshade demo, using color fill.
3
4        Maurice LeBrun
5        IFS, University of Texas at Austin
6        20 Mar 1994
7*)
8
9open Plplot
10
11
12(* Comment this out since Plot.colorbar which it wraps sets a color and removes it afterwards
13which causes problems when comparing results with other languages.
14
15let colorbar ?color ?contour values =
16  (* Smaller text *)
17  plschr 0.0 0.75;
18  (* Small ticks on the vertical axis *)
19  plsmaj 0.0 0.5;
20  plsmin 0.0 0.5;
21
22  let axis =
23    [
24      `frame0;
25      `frame1;
26      `vertical_label;
27      `unconventional_label;
28      `major_ticks;
29    ]
30  in
31  let shade = Plot.shade_colorbar ~custom:true ~axis values in
32  let pos = Plot.viewport_pos ~inside:false 0.005 0.0 in
33  Plot.plot [
34    Plot.colorbar ?color ?contour ~orient:(`top (0.0375, 0.875)) ~label:[`bottom "Magnitude"] ~pos shade;
35  ];
36
37  (* Reset text and tick sizes *)
38  plschr 0.0 1.0;
39  plsmaj 0.0 1.0;
40  plsmin 0.0 1.0
41
42end of commented out colorbar.  *)
43
44(* Define my_colorbar as a convenience for this example with all fixed arguments used
45for all plcolorbar calls defined here in one place.  In addition this function
46sets and restores text and tick sizes before and after the plcolorball call. *)
47
48let my_colorbar cont_color cont_width shedge =
49  (* Smaller text *)
50  plschr 0.0 0.75;
51  (* Small ticks on the vertical axis *)
52  plsmaj 0.0 0.5;
53  plsmin 0.0 0.5;
54
55  (* Fixed arguments for this entire example. *)
56  let x = 0.005 in
57  let y = 0.0 in
58  let x_length = 0.0375 in
59  let y_length = 0.875 in
60  let bg_color = 0 in
61  let bb_color = 1 in
62  let bb_style = 1 in
63  let low_cap_color = 0.0 in
64  let high_cap_color = 0.0 in
65  let label_opts = [| [PL_COLORBAR_LABEL_BOTTOM] |] in
66  let labels = [|"Magnitude"|] in
67  let axis_strings = [|"bcvtm"|] in
68  let tick_spacing = [|0.0|] in
69  let sub_ticks = [|0|] in
70  let values = Array.make 1 shedge in
71
72  ignore (
73  plcolorbar [PL_COLORBAR_SHADE ; PL_COLORBAR_SHADE_LABEL] []
74    x y x_length y_length bg_color bb_color bb_style low_cap_color high_cap_color
75    cont_color cont_width
76    label_opts labels
77    axis_strings tick_spacing sub_ticks values
78  );
79
80  (* Reset text and tick sizes *)
81  plschr 0.0 1.0;
82  plsmaj 0.0 1.0;
83  plsmin 0.0 1.0
84
85let pi = atan 1.0 *. 4.0
86
87(* Fundamental settings.  See notes[] for more info. *)
88
89let ns = 20             (* Default number of shade levels *)
90let nx = 35             (* Default number of data points in x *)
91let ny = 46             (* Default number of data points in y *)
92let exclude = false     (* By default do not plot a page illustrating
93                           exclusion. *)
94
95(* polar plot data *)
96let perimeterpts = 100
97
98(* Transformation function *)
99let mypltr x y tr =
100  tr.(0) *. x +. tr.(1) *. y +. tr.(2),
101  tr.(3) *. x +. tr.(4) *. y +. tr.(5)
102
103let zdefined x y =
104  let z = sqrt (x *. x +. y *. y) in
105  if z < 0.4 || z > 0.6 then 1 else 0
106
107(*--------------------------------------------------------------------------*\
108 * f2mnmx
109 *
110 * Returns min & max of input 2d array.
111\*--------------------------------------------------------------------------*)
112let f2mnmx f =
113  let fmax = ref f.(0).(0) in
114  let fmin = ref f.(0).(0) in
115  for i = 0 to Array.length f - 1 do
116    for j = 0 to Array.length f.(i) - 1 do
117      fmax := max !fmax f.(i).(j);
118      fmin := min !fmin f.(i).(j);
119    done
120  done;
121  !fmin, !fmax
122
123(*--------------------------------------------------------------------------*\
124 * Does several shade plots using different coordinate mappings.
125\*--------------------------------------------------------------------------*)
126let () =
127  let fill_width = 2.0 in
128  let cont_color = 0 in
129  let cont_width = 0.0 in
130
131  (* Parse and process command line arguments *)
132  plparseopts Sys.argv [PL_PARSE_FULL];
133
134  (* Load color palettes *)
135  plspal0 "cmap0_black_on_white.pal";
136  plspal1 "cmap1_gray.pal" true;
137
138  (* Reduce colors in cmap 0 so that cmap 1 is useful on a 16-color display *)
139  plscmap0n 3;
140
141  (* Initialize plplot *)
142  plinit ();
143
144  (* Set up transformation function *)
145  let tr =
146    [|
147      2.0 /. float_of_int (nx - 1); 0.0; -1.0;
148      0.0; 2.0 /. float_of_int (ny-1); -1.0;
149    |]
150  in
151
152  (* Set up data arrays *)
153  let z = Array.make_matrix nx ny 0.0 in
154  let w = Array.make_matrix nx ny 0.0 in
155  for i = 0 to nx - 1 do
156    let x = float_of_int (i - (nx / 2)) /. float_of_int (nx / 2) in
157    for j = 0 to ny - 1 do
158      let y = float_of_int (j - (ny / 2)) /. float_of_int (ny / 2) -. 1.0 in
159      z.(i).(j) <- -. sin (7.0 *. x) *. cos (7.0 *. y) +. x *. x -. y *. y;
160      w.(i).(j) <- -. cos (7.0 *. x) *. sin (7.0 *. y) +. 2.0 *. x *. y;
161    done
162  done;
163
164  let zmin, zmax = f2mnmx z in
165  let clevel =
166    Array.init ns (
167      fun i ->
168        zmin +. (zmax -. zmin) *. (float_of_int i +. 0.5) /. float_of_int ns
169    )
170  in
171  let shedge =
172    Array.init (ns + 1) (
173      fun i ->
174        zmin +. (zmax -. zmin) *. float_of_int i /. float_of_int ns
175    )
176  in
177
178  (* Set up coordinate grids *)
179  let xg1 = Array.make nx 0.0 in
180  let yg1 = Array.make ny 0.0 in
181  let xg2 = Array.make_matrix nx ny 0.0 in
182  let yg2 = Array.make_matrix nx ny 0.0 in
183
184  for i = 0 to nx - 1 do
185    for j = 0 to ny - 1 do
186      let x, y = mypltr (float_of_int i) (float_of_int j) tr in
187
188      let argx = x *. pi /. 2.0 in
189      let argy = y *. pi /. 2.0 in
190      let distort = 0.4 in
191
192      xg1.(i) <- x +. distort *. cos argx;
193      yg1.(j) <- y -. distort *. cos argy;
194
195      xg2.(i).(j) <- x +. distort *. cos argx *. cos argy;
196      yg2.(i).(j) <- y -. distort *. cos argx *. cos argy;
197    done
198  done;
199
200  (* Plot using identity transform *)
201  pladv 0;
202  plvpor 0.1 0.9 0.1 0.9;
203  plwind (-1.0) 1.0 (-1.0) 1.0;
204
205  plpsty 0;
206
207  plshades z (-1.0) 1.0 (-1.0) 1.0 shedge fill_width cont_color cont_width true;
208
209  my_colorbar 0 0.0 shedge;
210
211  plcol0 1;
212  plbox "bcnst" 0.0 0 "bcnstv" 0.0 0;
213  plcol0 2;
214  pllab "distance" "altitude" "Bogon density";
215
216  (* Plot using 1d coordinate transform *)
217
218  (* Load color palettes *)
219  plspal0 "cmap0_black_on_white.pal";
220  plspal1 "cmap1_blue_yellow.pal" true;
221
222  pladv 0;
223  plvpor 0.1 0.9 0.1 0.9;
224  plwind (-1.0) 1.0 (-1.0) 1.0;
225
226  plpsty 0;
227
228  plset_pltr (pltr1 xg1 yg1);
229  plshades z (-1.0) 1.0 (-1.0) 1.0 shedge fill_width cont_color cont_width true;
230
231  my_colorbar 0 0.0 shedge;
232
233  plcol0 1;
234  plbox "bcnst" 0.0 0 "bcnstv" 0.0 0;
235  plcol0 2;
236  pllab "distance" "altitude" "Bogon density";
237
238  (* Plot using 2d coordinate transform *)
239
240  (* Load color palettes *)
241  plspal0 "cmap0_black_on_white.pal";
242  plspal1 "cmap1_blue_red.pal" true;
243
244  pladv 0;
245  plvpor 0.1 0.9 0.1 0.9;
246  plwind (-1.0) 1.0 (-1.0) 1.0;
247
248  plpsty 0;
249
250  plset_pltr (pltr2 xg2 yg2);
251  plshades
252    z (-1.0) 1.0 (-1.0) 1.0 shedge fill_width cont_color cont_width false;
253
254  my_colorbar 0 0.0 shedge;
255
256  plcol0 1;
257  plbox "bcnst" 0.0 0 "bcnstv" 0.0 0;
258  plcol0 2;
259  plcont w 1 nx 1 ny clevel;
260
261  pllab "distance" "altitude" "Bogon density, with streamlines";
262
263  (* Plot using 2d coordinate transform *)
264
265  (* Load color palettes *)
266  plspal0 "";
267  plspal1 "" true;
268
269  pladv 0;
270  plvpor 0.1 0.9 0.1 0.9;
271  plwind (-1.0) 1.0 (-1.0) 1.0;
272
273  plpsty 0;
274
275  plshades z (-1.0) 1.0 (-1.) 1.0 shedge fill_width 2 3.0 false;
276
277  my_colorbar 2 3.0 shedge;
278
279  plcol0 1;
280  plbox "bcnst" 0.0 0 "bcnstv" 0.0 0;
281  plcol0 2;
282
283  pllab "distance" "altitude" "Bogon density";
284
285  (* Note this exclusion API will probably change. *)
286
287  (* Plot using 2d coordinate transform and exclusion*)
288  if exclude then (
289    pladv 0;
290    plvpor 0.1 0.9 0.1 0.9;
291    plwind (-1.0) 1.0 (-1.0) 1.0;
292
293    plpsty 0;
294
295    plset_defined zdefined;
296    plshades
297      z (-1.0) 1.0 (-1.0) 1.0 shedge fill_width cont_color cont_width false;
298
299    my_colorbar 0 0.0 shedge;
300    plunset_defined ();
301
302    plcol0 1;
303    plbox "bcnst" 0.0 0 "bcnstv" 0.0 0;
304
305    pllab "distance" "altitude" "Bogon density with exclusion";
306  );
307  (* Example with polar coordinates. *)
308
309  (* Load colour palettes*)
310  plspal0 "cmap0_black_on_white.pal";
311  plspal1 "cmap1_gray.pal" true;
312
313  pladv 0;
314  plvpor 0.1 0.9 0.1 0.9;
315  plwind (-1.0) 1.0 (-1.0) 1.0;
316  plpsty 0;
317
318  (* Build new coordinate matrices. *)
319  for i = 0 to nx - 1 do
320    let r = float_of_int i /. float_of_int (nx - 1) in
321    for j = 0 to ny - 1 do
322      let t = (2.0 *. pi /. (float_of_int ny -. 1.0)) *. float_of_int j in
323      xg2.(i).(j) <- r *. cos t;
324      yg2.(i).(j) <- r *. sin t;
325      z.(i).(j) <- exp (~-.r *. r) *. cos (5.0 *. pi *. r) *. cos (5.0 *. t);
326    done
327  done;
328
329  (* Need a new shedge to go along with the new data set. *)
330  let zmin, zmax = f2mnmx z in
331
332  let shedge =
333    Array.init (ns + 1) (
334      fun i ->
335        zmin +. (zmax -. zmin) *. float_of_int i /. float_of_int ns
336    )
337  in
338
339  (*  Now we can shade the interior region. *)
340  plshades
341    z (-1.0) 1.0 (-1.0) 1.0 shedge fill_width cont_color cont_width false;
342
343  my_colorbar 0 0.0 shedge;
344
345  (* Now we can draw the perimeter.  (If do before, shade stuff may overlap.) *)
346  let px = Array.make perimeterpts 0.0 in
347  let py = Array.make perimeterpts 0.0 in
348  for i = 0 to perimeterpts - 1 do
349    let t = (2.0 *. pi /. float_of_int (perimeterpts - 1)) *. float_of_int i in
350    px.(i) <- cos t;
351    py.(i) <- sin t;
352  done;
353  plcol0 1;
354  plline px py;
355
356  (* And label the plot.*)
357  plcol0 2;
358  pllab "" "" "Tokamak Bogon Instability";
359
360  (* Clean up *)
361  plend ();
362  ()
363
364