1(*
2Demonstrate most pllegend capability including unicode symbols.
3
4Copyright (C) 2010-2018 Alan W. Irwin
5Copyright (C) 2011 Hezekiah M. Carty
6
7This file is part of PLplot.
8
9PLplot is free software; you can redistribute it and/or modify
10it under the terms of the GNU Library General Public License as published
11by the Free Software Foundation; either version 2 of the License, or
12(at your option) any later version.
13
14PLplot is distributed in the hope that it will be useful,
15but WITHOUT ANY WARRANTY; without even the implied warranty of
16MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17GNU Library General Public License for more details.
18
19You should have received a copy of the GNU Library General Public License
20along with PLplot; if not, write to the Free Software
21Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA *)
22
23(* This example designed just for devices (e.g., the cairo-related and
24   qt-related devices) where the best choice of glyph is automatically
25   selected by the related libraries (pango/cairo or Qt4) for each
26   unicode character depending on what system fonts are installed.  Of
27   course, you must have the appropriate TrueType fonts installed to
28   have access to all the required glyphs. *)
29
30open Plplot
31open Printf
32
33let position_options = [|
34  [PL_POSITION_LEFT; PL_POSITION_TOP; PL_POSITION_OUTSIDE];
35  [PL_POSITION_TOP; PL_POSITION_OUTSIDE];
36  [PL_POSITION_RIGHT; PL_POSITION_TOP; PL_POSITION_OUTSIDE];
37  [PL_POSITION_RIGHT; PL_POSITION_OUTSIDE];
38  [PL_POSITION_RIGHT; PL_POSITION_BOTTOM; PL_POSITION_OUTSIDE];
39  [PL_POSITION_BOTTOM; PL_POSITION_OUTSIDE];
40  [PL_POSITION_LEFT; PL_POSITION_BOTTOM; PL_POSITION_OUTSIDE];
41  [PL_POSITION_LEFT; PL_POSITION_OUTSIDE];
42  [PL_POSITION_LEFT; PL_POSITION_TOP; PL_POSITION_INSIDE];
43  [PL_POSITION_TOP; PL_POSITION_INSIDE];
44  [PL_POSITION_RIGHT; PL_POSITION_TOP; PL_POSITION_INSIDE];
45  [PL_POSITION_RIGHT; PL_POSITION_INSIDE];
46  [PL_POSITION_RIGHT; PL_POSITION_BOTTOM; PL_POSITION_INSIDE];
47  [PL_POSITION_BOTTOM; PL_POSITION_INSIDE];
48  [PL_POSITION_LEFT; PL_POSITION_BOTTOM; PL_POSITION_INSIDE];
49  [PL_POSITION_LEFT; PL_POSITION_INSIDE];
50|]
51
52(* Pick 5 arbitrary UTF-8 symbols useful for plotting points (✠✚✱✪✽✺✰✴✦). *)
53let special_symbols = [|
54  "✰";
55  "✴";
56  "✱";
57  "✽";
58  "✦";
59|]
60
61(* plcolorbar options *)
62
63(* Colorbar type options *)
64let colorbar_kinds = 4
65let colorbar_option_kinds = [|
66  [PL_COLORBAR_SHADE];
67  [PL_COLORBAR_SHADE; PL_COLORBAR_SHADE_LABEL];
68  [PL_COLORBAR_IMAGE];
69  [PL_COLORBAR_GRADIENT]
70|]
71
72let colorbar_option_kind_labels = [|
73  "Shade colorbars";
74  "Shade colorbars with custom labels";
75  "Image colorbars";
76  "Gradient colorbars"
77|]
78
79(* Which side of the page are we positioned relative to? *)
80let colorbar_positions = 4
81let colorbar_position_options = [|
82  [PL_POSITION_LEFT];
83  [PL_POSITION_RIGHT];
84  [PL_POSITION_TOP];
85  [PL_POSITION_BOTTOM]
86|]
87
88let colorbar_position_option_labels = [|
89  "Left";
90  "Right";
91  "Top";
92  "Bottom"
93|]
94
95(* Colorbar label positioning options *)
96let colorbar_labels = 4
97let colorbar_label_options = [|
98  [PL_COLORBAR_LABEL_LEFT];
99  [PL_COLORBAR_LABEL_RIGHT];
100  [PL_COLORBAR_LABEL_TOP];
101  [PL_COLORBAR_LABEL_BOTTOM]
102|]
103
104let colorbar_label_option_labels = [|
105  "Label left";
106  "Label right";
107  "Label top";
108  "Label bottom"
109|]
110
111(* Colorbar cap options *)
112let colorbar_caps = 4
113let colorbar_cap_options = [|
114  [PL_COLORBAR_CAP_NONE];
115  [PL_COLORBAR_CAP_LOW];
116  [PL_COLORBAR_CAP_HIGH];
117  [PL_COLORBAR_CAP_LOW;PL_COLORBAR_CAP_HIGH]
118|]
119
120let colorbar_cap_option_labels = [|
121  "No caps";
122  "Low cap";
123  "High cap";
124  "Low and high caps"
125|]
126
127let plcolorbar_example_page kind_i label_i cap_i cont_color cont_width values_vector =
128
129  pladv 0;
130  (* Draw one colorbar relative to each side of the page *)
131  for position_i = 0 to colorbar_positions - 1 do
132
133    (* Smaller text *)
134    plschr 0.0 0.75;
135    (* Small ticks on the vertical axis *)
136    plsmaj 0.0 0.5;
137    plsmin 0.0 0.5;
138
139    plvpor 0.20 0.80 0.20 0.80;
140    plwind 0.0 1.0 0.0 1.0;
141    (* Set interesting background colour. *)
142    plscol0a 15 0 0 0 0.20;
143
144    (* Colorbar parameters *)
145    let opt = colorbar_option_kinds.(kind_i) @ colorbar_label_options.(label_i) @ colorbar_cap_options.(cap_i) @ [PL_COLORBAR_BOUNDING_BOX ; PL_COLORBAR_BACKGROUND] in
146
147    let position = colorbar_position_options.(position_i) in
148
149    let vertical = List.mem PL_POSITION_LEFT position || List.mem PL_POSITION_RIGHT position in
150    let ifn = List.mem PL_POSITION_LEFT position || List.mem PL_POSITION_BOTTOM position in
151
152    (* Set the offset position on the page *)
153    let x = 0. in
154    let y = 0. in
155    let x_length = if vertical then 0.05 else 0.5 in
156    let y_length = if vertical then 0.5 else 0.05 in
157
158    let bg_color = 15 in
159    let bb_color = 1 in
160    let bb_style = 1 in
161    let low_cap_color = 0.0 in
162    let high_cap_color = 1.0 in
163    let label_opts = [| [PL_COLORBAR_NULL] |] in
164    let labels = [| colorbar_position_option_labels.(position_i) ^ ", " ^ colorbar_label_option_labels.(label_i) |] in
165
166    (* equivalent C code
167       if ( ifn )
168       {
169       if ( cont_color == 0 || cont_width == 0. )
170       {
171       axis_opts[0] = "uwtivn";
172       //axis_opts[0] = "uwtin";
173       }
174       else
175       {
176       axis_opts[0] = "uwxvn";
177       //axis_opts[0] = "uwxn";
178       }
179       }
180       else
181       {
182       if ( cont_color == 0 || cont_width == 0. )
183       {
184       axis_opts[0] = "uwtivm";
185       //axis_opts[0] = "uwtim";
186       }
187       else
188       {
189       axis_opts[0] = "uwxvm";
190       //axis_opts[0] = "uwxm";
191       }
192       }
193     *)
194
195    let axis_opts = [|
196      if
197	(ifn && ( cont_color = 0 || cont_width = 0.)) then "uwtivn"
198      else if
199	(ifn && not ( cont_color = 0 || cont_width = 0.)) then "uwxvn"
200      else if
201	(not ifn && ( cont_color = 0 || cont_width = 0.)) then "uwtivm"
202      else if
203	(not ifn && not ( cont_color = 0 || cont_width = 0.)) then "uwxvm"
204      else("")
205    |] in
206
207    let tick_spacing = [|0.0|] in
208    let sub_ticks = [|0|] in
209    let values_matrix = Array.make 1 values_vector in
210
211    ignore (
212    plcolorbar opt position
213      x y x_length y_length bg_color bb_color bb_style low_cap_color high_cap_color
214      cont_color cont_width
215      label_opts labels
216      axis_opts tick_spacing sub_ticks values_matrix
217   );
218
219    (* Reset text and tick sizes *)
220    plschr 0.0 1.0;
221    plsmaj 0.0 1.0;
222    plsmin 0.0 1.0
223  done;
224
225  (* Draw a page title *)
226  let title = colorbar_option_kind_labels.(kind_i) ^ " - " ^ colorbar_cap_option_labels.(cap_i) in
227  plvpor 0.0 1.0 0.0 1.0;
228  plwind 0.0 1.0 0.0 1.0;
229  plptex 0.5 0.5 0.0 0.0 0.5 title
230
231let plcolorbar_example palette kind_i cont_color cont_width values =
232
233    (* Load the color palette *)
234    plspal1 palette true;
235
236  for label_i = 0 to colorbar_labels - 1 do
237    for cap_i = 0 to colorbar_caps - 1 do
238      plcolorbar_example_page kind_i label_i cap_i cont_color cont_width values;
239    done;
240  done
241
242(* main
243   Demonstrate most pllegend capability including unicode symbols. *)
244
245let max_nlegend = 7
246
247let () =
248  let opt_array = Array.make max_nlegend [] in
249  let box_colors = Array.make max_nlegend 0 in
250  let box_patterns = Array.make max_nlegend 0 in
251  let box_scales = Array.make max_nlegend 0.0 in
252  let box_line_widths = Array.make max_nlegend 0.0 in
253  let line_colors = Array.make max_nlegend 0 in
254  let line_styles = Array.make max_nlegend 0 in
255  let line_widths = Array.make max_nlegend 0.0 in
256  let symbol_numbers = Array.make max_nlegend 0 in
257  let symbol_colors = Array.make max_nlegend 0 in
258  let symbol_scales = Array.make max_nlegend 0.0 in
259  let symbols = Array.make max_nlegend "" in
260  let text = Array.make max_nlegend "" in
261  let text_colors = Array.make max_nlegend 0 in
262
263  (* Parse and process command line arguments *)
264  plparseopts Sys.argv [PL_PARSE_FULL];
265
266  (* Initialize plplot *)
267  plinit ();
268
269  (* First page illustrating the 16 standard positions. *)
270  pladv 0;
271  plvpor 0.25 0.75 0.25 0.75;
272  plwind 0.0 1.0 0.0 1.0;
273  plbox "bc" 0.0 0 "bc" 0.0 0;
274  plsfont PL_FCI_SANS PL_FCI_STYLE_UNCHANGED PL_FCI_WEIGHT_UNCHANGED;
275  plmtex "t" 8.0 0.5 0.5 "The 16 standard legend positions with";
276  plmtex "t" 6.0 0.5 0.5 "the same (0.05) offset in x and y";
277
278  let nlegend = 1 in
279  (* Only specify legend data that are required according to the
280     value of opt_array for that entry. *)
281  let opt_base = [PL_LEGEND_BACKGROUND; PL_LEGEND_BOUNDING_BOX] in
282  opt_array.(0) <- [PL_LEGEND_LINE; PL_LEGEND_SYMBOL];
283  line_styles.(0) <- 1;
284  line_widths.(0) <- 1.0;
285  symbol_scales.(0) <- 1.;
286  symbol_numbers.(0) <- 4;
287  symbols.(0) <- "#(728)";
288
289  (* Use monotype fonts so that all legends are the same size. *)
290  plsfont PL_FCI_MONO PL_FCI_STYLE_UNCHANGED PL_FCI_WEIGHT_UNCHANGED;
291  plscol0a 15 32 32 32 0.70;
292
293  for k = 0 to 15 do
294    let opt_array = Array.sub opt_array 0 nlegend in
295    let position = position_options.(k) in
296    let opt = opt_base in
297    text.(0) <- sprintf "%2.2d" k;
298    text_colors.(0) <- 1 + ( k mod 8 );
299    line_colors.(0) <- 1 + ( k mod 8 );
300    symbol_colors.(0) <- 1 + ( k mod 8 );
301
302    ignore (
303      pllegend opt position 0.05 0.05
304          0.1 15 1 1 0 0
305          opt_array 1.0 1.0 2.0
306          1.0 text_colors text
307          [||] [||] [||] [||]
308          line_colors line_styles line_widths
309          symbol_colors symbol_scales symbol_numbers symbols
310    );
311  done;
312
313  (* Second page illustrating effect of nrow, ncolumn for the same legend
314     data. *)
315  pladv 0;
316  plvpor 0.25 0.75 0.25 0.75;
317  plwind 0.0 1.0 0.0 1.0;
318  plbox "bc" 0.0 0 "bc" 0.0 0;
319  plsfont PL_FCI_SANS PL_FCI_STYLE_UNCHANGED PL_FCI_WEIGHT_UNCHANGED;
320  plmtex "t" 8.0 0.5 0.5 "The effect of nrow, ncolumn, PL_LEGEND_ROW_MAJOR,";
321  plmtex "t" 6.0 0.5 0.5 "and position for the same legend data";
322
323  let nlegend = 7 in
324
325  (* Only specify legend data that are required according to the
326     value of opt_array for that entry. *)
327  let opt_base = [PL_LEGEND_BACKGROUND; PL_LEGEND_BOUNDING_BOX] in
328  for k = 0 to nlegend - 1 do
329    opt_array.(k) <- [PL_LEGEND_LINE; PL_LEGEND_SYMBOL];
330    line_styles.(k) <- 1;
331    line_widths.(k) <- 1.0;
332    symbol_scales.(k) <- 1.0;
333    symbol_numbers.(k) <- 2;
334    symbols.(k) <- "#(728)";
335    text.(k) <- sprintf "%2.2d" k;
336    text_colors.(k) <- 1 + (k mod 8);
337    line_colors.(k) <- 1 + (k mod 8);
338    symbol_colors.(k) <- 1 + (k mod 8);
339  done;
340
341  (* Use monotype fonts so that all legends are the same size. *)
342  plsfont PL_FCI_MONO PL_FCI_STYLE_UNCHANGED PL_FCI_WEIGHT_UNCHANGED;
343  plscol0a 15 32 32 32 0.70;
344
345  let position = [PL_POSITION_TOP; PL_POSITION_OUTSIDE] in
346  let opt = opt_base in
347  let x = 0.0 in
348  let y = 0.1 in
349  let nrow = 1 in
350  let ncolumn = nlegend in
351  ignore (
352    let opt_array = Array.sub opt_array 0 nlegend in
353    pllegend opt position x y
354        0.05 15 1 1 nrow ncolumn
355        opt_array 1.0 1.0 2.0
356        1.0 text_colors text
357        [||] [||] [||] [||]
358        line_colors line_styles line_widths
359        symbol_colors symbol_scales symbol_numbers symbols;
360  );
361
362  let position = [PL_POSITION_BOTTOM; PL_POSITION_OUTSIDE] in
363  let opt = opt_base in
364  let x = 0.0 in
365  let y = 0.1 in
366  let nrow = 1 in
367  let ncolumn = nlegend in
368  ignore (
369    let opt_array = Array.sub opt_array 0 nlegend in
370    pllegend opt position x y
371        0.05 15 1 1 nrow ncolumn
372        opt_array 1.0 1.0 2.0
373        1.0 text_colors text
374        [||] [||] [||] [||]
375        line_colors line_styles line_widths
376        symbol_colors symbol_scales symbol_numbers symbols
377  );
378
379  let position = [PL_POSITION_LEFT; PL_POSITION_OUTSIDE] in
380  let opt = opt_base in
381  let x = 0.1 in
382  let y = 0.0 in
383  let nrow = nlegend in
384  let ncolumn = 1 in
385  ignore (
386    let opt_array = Array.sub opt_array 0 nlegend in
387    pllegend opt position x y
388        0.05 15 1 1 nrow ncolumn
389        opt_array 1.0 1.0 2.0
390        1.0 text_colors text
391        [||] [||] [||] [||]
392        line_colors line_styles line_widths
393        symbol_colors symbol_scales symbol_numbers symbols;
394  );
395
396  let position = [PL_POSITION_RIGHT; PL_POSITION_OUTSIDE] in
397  let opt = opt_base in
398  let x = 0.1 in
399  let y = 0.0 in
400  let nrow = nlegend in
401  let ncolumn = 1 in
402  ignore (
403    let opt_array = Array.sub opt_array 0 nlegend in
404    pllegend opt position x y
405        0.05 15 1 1 nrow ncolumn
406        opt_array 1.0 1.0 2.0
407        1.0 text_colors text
408        [||] [||] [||] [||]
409        line_colors line_styles line_widths
410        symbol_colors symbol_scales symbol_numbers symbols
411  );
412
413  let position = [PL_POSITION_LEFT; PL_POSITION_TOP; PL_POSITION_INSIDE] in
414  let opt = opt_base in
415  let x = 0.0 in
416  let y = 0.0 in
417  let nrow = 6 in
418  let ncolumn = 2 in
419  ignore (
420    let opt_array = Array.sub opt_array 0 nlegend in
421    pllegend opt position x y
422        0.05 15 1 1 nrow ncolumn
423        opt_array 1.0 1.0 2.0
424        1.0 text_colors text
425        [||] [||] [||] [||]
426        line_colors line_styles line_widths
427        symbol_colors symbol_scales symbol_numbers symbols
428  );
429
430  let position = [PL_POSITION_RIGHT; PL_POSITION_TOP; PL_POSITION_INSIDE] in
431  let opt = PL_LEGEND_ROW_MAJOR :: opt_base in
432  let x = 0.0 in
433  let y = 0.0 in
434  let nrow = 6 in
435  let ncolumn = 2 in
436  ignore (
437    let opt_array = Array.sub opt_array 0 nlegend in
438    pllegend opt position x y
439        0.05 15 1 1 nrow ncolumn
440        opt_array 1.0 1.0 2.0
441        1.0 text_colors text
442        [||] [||] [||] [||]
443        line_colors line_styles line_widths
444        symbol_colors symbol_scales symbol_numbers symbols
445  );
446
447  let position = [PL_POSITION_BOTTOM; PL_POSITION_INSIDE] in
448  let opt = PL_LEGEND_ROW_MAJOR :: opt_base in
449  let x = 0.0 in
450  let y = 0.0 in
451  let nrow = 3 in
452  let ncolumn = 3 in
453  ignore (
454    let opt_array = Array.sub opt_array 0 nlegend in
455    pllegend opt position x y
456        0.05 15 1 1 nrow ncolumn
457        opt_array 1.0 1.0 2.0
458        1.0 text_colors text
459        [||] [||] [||] [||]
460        line_colors line_styles line_widths
461        symbol_colors symbol_scales symbol_numbers symbols
462  );
463
464  (* Third page demonstrating legend alignment *)
465  pladv 0;
466  plvpor 0.0 1.0 0.0 0.9;
467  plwind 0.0 1.0 0.0 1.0;
468  plsfont PL_FCI_SANS PL_FCI_STYLE_UNCHANGED PL_FCI_WEIGHT_UNCHANGED;
469  plmtex "t" 2.0 0.5 0.5 "Demonstrate legend alignment";
470
471  let x = ref 0.1 in
472  let y = ref 0.1 in
473  let nturn = 4 in
474  let nlegend = ref 0 in
475  let position = ref [PL_POSITION_TOP; PL_POSITION_LEFT; PL_POSITION_SUBPAGE] in
476  let opt_base = [PL_LEGEND_BACKGROUND; PL_LEGEND_BOUNDING_BOX] in
477  let opt = ref opt_base in
478  for i = 0 to 8 do
479    (* Set up legend arrays with the correct size, type. *)
480    if i <= nturn then
481      incr nlegend
482    else
483      decr nlegend;
484    nlegend := max 1 !nlegend;
485    (* Only specify legend data that are required according to the
486       value of opt_array for that entry. *)
487    for k = 0 to !nlegend - 1 do
488      opt_array.(k) <- [PL_LEGEND_LINE; PL_LEGEND_SYMBOL];
489      line_styles.(k) <- 1;
490      line_widths.(k) <- 1.0;
491      symbol_scales.(k) <- 1.;
492      symbol_numbers.(k) <- 2;
493      symbols.(k) <- "#(728)";
494      text.(k) <- sprintf "%2.2d" k;
495      text_colors.(k) <- 1 + (k mod 8);
496      line_colors.(k) <- 1 + (k mod 8);
497      symbol_colors.(k) <- 1 + (k mod 8);
498    done;
499    (* Use monotype fonts so that all legends are the same size. *)
500    plsfont PL_FCI_MONO PL_FCI_STYLE_UNCHANGED PL_FCI_WEIGHT_UNCHANGED;
501    plscol0a 15 32 32 32 0.70;
502
503    let nrow = min 3 !nlegend in
504    let ncolumn = 0 in
505
506    let legend_width, legend_height =
507      let opt_array = Array.sub opt_array 0 !nlegend in
508      pllegend !opt !position !x !y
509          0.025 15 1 1 nrow ncolumn
510          opt_array 1.0 1.0 1.5
511          1.0 text_colors text
512          [||] [||] [||] [||]
513          line_colors line_styles line_widths
514          symbol_colors symbol_scales symbol_numbers symbols
515    in
516
517    if i = nturn then (
518      position := [PL_POSITION_TOP; PL_POSITION_RIGHT; PL_POSITION_SUBPAGE];
519      opt := opt_base;
520      x := 1.0 -. !x;
521      y := !y +. legend_height;
522    )
523    else (
524      x := !x +. legend_width;
525      y := !y +. legend_height;
526    );
527  done;
528
529  (* Fourth page illustrating various kinds of legends *)
530  let max_height = 0.0 in
531  let xstart = 0.0 in
532  let ystart = 0.1 in
533  let x = xstart in
534  let y = ystart in
535  let text_scale = 0.90 in
536  pladv 0;
537  plvpor 0.0 1.0 0.0 0.90;
538  plwind 0.0 1.0 0.0 1.0;
539  plsfont PL_FCI_SANS PL_FCI_STYLE_UNCHANGED PL_FCI_WEIGHT_UNCHANGED;
540  plmtex "t" 2.0 0.5 0.5 "Demonstrate Various Kinds of Legends";
541
542  let nlegend = 5 in
543  (* Only specify legend data that are required according to the
544     value of opt_array for that entry. *)
545  let position = [PL_POSITION_LEFT; PL_POSITION_TOP] in
546  let opt_base = [PL_LEGEND_BACKGROUND; PL_LEGEND_BOUNDING_BOX; PL_LEGEND_TEXT_LEFT] in
547
548  (* Set up None, Box, Line, Symbol, and Line & Symbol legend entries. *)
549  opt_array.(0) <- [PL_LEGEND_NONE];
550  text.(0) <- sprintf "%s" "None";
551  text_colors.(0) <- 1;
552
553  opt_array.(1) <- [PL_LEGEND_COLOR_BOX];
554  text.(1) <- sprintf "%s" "Box";
555  text_colors.(1) <- 2;
556  box_colors.(1) <- 2;
557  box_patterns.(1) <- 0;
558  box_scales.(1) <- 0.8;
559  box_line_widths.(1) <- 1.0;
560
561  opt_array.(2) <- [PL_LEGEND_LINE];
562  text.(2) <- sprintf "%s" "Line";
563  text_colors.(2) <- 3;
564  line_colors.(2) <- 3;
565  line_styles.(2) <- 1;
566  line_widths.(2) <- 1.0;
567
568  opt_array.(3) <- [PL_LEGEND_SYMBOL];
569  text.(3) <- sprintf "%s" "Symbol";
570  text_colors.(3) <- 4;
571  symbol_colors.(3) <- 4;
572  symbol_scales.(3) <- text_scale;
573  symbol_numbers.(3) <- 4;
574  symbols.(3) <- special_symbols.(2);
575
576  opt_array.(4) <- [PL_LEGEND_SYMBOL; PL_LEGEND_LINE];
577  text.(4) <- sprintf "%s" "L & S";
578  text_colors.(4) <- 5;
579  line_colors.(4) <- 5;
580  line_styles.(4) <- 1;
581  line_widths.(4) <- 1.0;
582  symbol_colors.(4) <- 5;
583  symbol_scales.(4) <- text_scale;
584  symbol_numbers.(4) <- 4;
585  symbols.(4) <- special_symbols.(2);
586
587  let opt = opt_base in
588  plscol0a 15 32 32 32 0.70;
589
590  let legend_width, legend_height =
591    let opt_array = Array.sub opt_array 0 nlegend in
592    pllegend opt position x y
593        0.1 15 1 1 0 0
594        opt_array 1.0 text_scale 2.0
595        0.0 text_colors text
596        box_colors box_patterns box_scales box_line_widths
597        line_colors line_styles line_widths
598        symbol_colors symbol_scales symbol_numbers symbols
599  in
600  let max_height = max max_height legend_height in
601
602  (* Set up symbol legend entries with various symbols. *)
603  for i = 0 to nlegend - 1 do
604    opt_array.(i) <- [PL_LEGEND_SYMBOL];
605    text.(i) <- sprintf "%s%s" "Symbol " special_symbols.(i);
606    text_colors.(i) <- i + 1;
607    symbol_colors.(i) <- i + 1;
608    symbol_scales.(i) <- text_scale;
609    symbol_numbers.(i) <- 4;
610    symbols.(i) <- special_symbols.(i);
611  done;
612
613  let opt = opt_base in
614  let x = x +. legend_width in
615  plscol0a 15 32 32 32 0.70;
616
617  let legend_width, legend_height =
618    let opt_array = Array.sub opt_array 0 nlegend in
619    pllegend opt position x y
620        0.1 15 1 1 0 0
621        opt_array 1.0 text_scale 2.0
622        0.0 text_colors text
623        [||] [||] [||] [||]
624        [||] [||] [||]
625        symbol_colors symbol_scales symbol_numbers symbols
626  in
627  let max_height = max max_height legend_height in
628
629  (* Set up symbol legend entries with various numbers of symbols. *)
630  for i = 0 to nlegend - 1 do
631    opt_array.(i) <- [PL_LEGEND_SYMBOL];
632    text.(i) <- sprintf "%s %d" "Symbol Number" (i + 2);
633    text_colors.(i) <- i + 1;
634    symbol_colors.(i) <- i + 1;
635    symbol_scales.(i) <- text_scale;
636    symbol_numbers.(i) <- i + 2;
637    symbols.(i) <- special_symbols.(2);
638  done;
639
640  let opt = opt_base in
641  let x = x +. legend_width in
642  plscol0a 15 32 32 32 0.70;
643
644  let legend_width, legend_height =
645    let opt_array = Array.sub opt_array 0 nlegend in
646    pllegend opt position x y
647        0.1 15 1 1 0 0
648        opt_array 1.0 text_scale 2.0
649        0.0 text_colors text
650        [||] [||] [||] [||]
651        [||] [||] [||]
652        symbol_colors symbol_scales symbol_numbers symbols
653  in
654  let max_height = max max_height legend_height in
655
656  (* Set up box legend entries with various colours. *)
657  for i = 0 to nlegend - 1 do
658    opt_array.(i) <- [PL_LEGEND_COLOR_BOX];
659    text.(i) <- sprintf "%s %d" "Box Color" (i + 1);
660    text_colors.(i) <- i + 1;
661    box_colors.(i) <- i + 1;
662    box_patterns.(i) <- 0;
663    box_scales.(i) <- 0.8;
664    box_line_widths.(i) <- 1.0;
665  done;
666
667  let opt = opt_base in
668  (* Use new origin *)
669  let x = xstart in
670  let y = y +. max_height in
671  let max_height = 0.0 in
672  plscol0a 15 32 32 32 0.70;
673
674  let legend_width, legend_height =
675    let opt_array = Array.sub opt_array 0 nlegend in
676    pllegend opt position x y
677        0.1 15 1 1 0 0
678        opt_array 1.0 text_scale 2.0
679        0.0 text_colors text
680        box_colors box_patterns box_scales box_line_widths
681        [||] [||] [||]
682        [||] [||] [||] [||]
683  in
684  let max_height = max max_height legend_height in
685
686  (* Set up box legend entries with various patterns. *)
687  for i = 0 to nlegend - 1 do
688    opt_array.(i) <- [PL_LEGEND_COLOR_BOX];
689    text.(i) <- sprintf "%s %d" "Box Pattern" i;
690    text_colors.(i) <- 2;
691    box_colors.(i) <- 2;
692    box_patterns.(i) <- i;
693    box_scales.(i) <- 0.8;
694    box_line_widths.(i) <- 1.0;
695  done;
696
697  let opt = opt_base in
698  let x = x +. legend_width in
699  plscol0a 15 32 32 32 0.70;
700
701  let legend_width, legend_height =
702    let opt_array = Array.sub opt_array 0 nlegend in
703    pllegend opt position x y
704        0.1 15 1 1 0 0
705        opt_array 1.0 text_scale 2.0
706        0.0 text_colors text
707        box_colors box_patterns box_scales box_line_widths
708        [||] [||] [||]
709        [||] [||] [||] [||]
710  in
711  let max_height = max max_height legend_height in
712
713  (* Set up box legend entries with various box pattern line widths. *)
714  for i = 0 to nlegend - 1 do
715    opt_array.(i) <- [PL_LEGEND_COLOR_BOX];
716    text.(i) <- sprintf "%s %d" "Box Line Width" (i + 1);
717    text_colors.(i) <- 2;
718    box_colors.(i) <- 2;
719    box_patterns.(i) <- 3;
720    box_scales.(i) <- 0.8;
721    box_line_widths.(i) <- float i +. 1.0;
722  done;
723
724  let opt = opt_base in
725  let x = x +. legend_width in
726  plscol0a 15 32 32 32 0.70;
727
728  let legend_width, legend_height =
729    let opt_array = Array.sub opt_array 0 nlegend in
730    pllegend opt position x y
731        0.1 15 1 1 0 0
732        opt_array 1.0 text_scale 2.0
733        0.0 text_colors text
734        box_colors box_patterns box_scales box_line_widths
735        [||] [||] [||]
736        [||] [||] [||] [||]
737  in
738  let max_height = max max_height legend_height in
739
740  (* Set up line legend entries with various colours. *)
741  for i = 0 to nlegend - 1 do
742    opt_array.(i) <- [PL_LEGEND_LINE];
743    text.(i) <- sprintf "%s %d" "Line Color" (i + 1);
744    text_colors.(i) <- i + 1;
745    line_colors.(i) <- i + 1;
746    line_styles.(i) <- 1;
747    line_widths.(i) <- 1.0;
748  done;
749
750  let opt = opt_base in
751  (* Use new origin *)
752  let x = xstart in
753  let y = y +. max_height in
754  let max_height = 0.0 in
755  plscol0a 15 32 32 32 0.70;
756
757  let legend_width, legend_height =
758    let opt_array = Array.sub opt_array 0 nlegend in
759    pllegend opt position x y
760        0.1 15 1 1 0 0
761        opt_array 1.0 text_scale 2.0
762        0.0 text_colors text
763        [||] [||] [||] [||]
764        line_colors line_styles line_widths
765        [||] [||] [||] [||]
766  in
767  let max_height = max max_height legend_height in
768
769  (* Set up line legend entries with various styles. *)
770  for i = 0 to nlegend - 1 do
771    opt_array.(i) <- [PL_LEGEND_LINE];
772    text.(i) <- sprintf "%s %d" "Line Style" (i + 1);
773    text_colors.(i) <- 2;
774    line_colors.(i) <- 2;
775    line_styles.(i) <- i + 1;
776    line_widths.(i) <- 1.0;
777  done;
778
779  let opt = opt_base in
780  let x = x +. legend_width in
781  plscol0a 15 32 32 32 0.70;
782
783  let legend_width, legend_height =
784    let opt_array = Array.sub opt_array 0 nlegend in
785    pllegend opt position x y
786        0.1 15 1 1 0 0
787        opt_array 1.0 text_scale 2.0
788        0.0 text_colors text
789        [||] [||] [||] [||]
790        line_colors line_styles line_widths
791        [||] [||] [||] [||]
792  in
793  let max_height = max max_height legend_height in
794
795  (* Set up line legend entries with various widths. *)
796  for i = 0 to nlegend - 1 do
797    opt_array.(i) <- [PL_LEGEND_LINE];
798    text.(i) <- sprintf "%s %d" "Line Width" (i + 1);
799    text_colors.(i) <- 2;
800    line_colors.(i) <- 2;
801    line_styles.(i) <- 1;
802    line_widths.(i) <- float i +. 1.0;
803  done;
804
805  let opt = opt_base in
806  let x = x +. legend_width in
807  plscol0a 15 32 32 32 0.70;
808
809  let legend_width, legend_height =
810    let opt_array = Array.sub opt_array 0 nlegend in
811    pllegend opt position x y
812        0.1 15 1 1 0 0
813        opt_array 1.0 text_scale 2.0
814        0.0 text_colors text
815        [||] [||] [||] [||]
816        line_colors line_styles line_widths
817        [||] [||] [||] [||]
818  in
819  let max_height = max max_height legend_height in
820  (* Silence a warning, so the reset is here once the plcolorbar pages are
821     added. *)
822  ignore (max_height);
823
824  (* Color bar examples *)
825
826  let values_small = [| -1.0e-20; 1.0e-20 |] in
827  let values_uneven = [| -1.0e-20; 2.0e-20; 2.6e-20; 3.4e-20; 6.0e-20; 7.0e-20; 8.0e-20; 9.0e-20; 10.0e-20 |] in
828  let values_even = [|-2.0e-20; -1.0e-20; 0.0e-20; 1.0e-20; 2.0e-20; 3.0e-20; 4.0e-20; 5.0e-20; 6.0e-20 |] in
829
830  (* Use unsaturated green background colour to contrast with black caps. *)
831  plscolbg 70 185 70;
832
833  (* Cut out the greatest and smallest bits of the color spectrum to
834     leave colors for the end caps. *)
835  plscmap1_range 0.01 0.99;
836
837  (* We can only test image and gradient colorbars with two element arrays *)
838  for i = 2 to colorbar_kinds - 1 do
839    plcolorbar_example "cmap1_blue_yellow.pal" i 0 0. values_small;
840  done;
841
842  (* Test shade colorbars with larger arrays *)
843  for i = 0 to 1 do
844    plcolorbar_example "cmap1_blue_yellow.pal" i 4 2. values_even;
845  done;
846
847  for i = 0 to 1 do
848    plcolorbar_example "cmap1_blue_yellow.pal" i 0 0. values_uneven;
849  done;
850
851  plend();
852  ()
853
854