File: x30.ml

package info (click to toggle)
plplot 5.15.0%2Bdfsg-19
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 31,312 kB
  • sloc: ansic: 79,707; xml: 28,583; cpp: 20,033; ada: 19,456; tcl: 12,081; f90: 11,431; ml: 7,276; java: 6,863; python: 6,792; sh: 3,274; perl: 828; lisp: 75; makefile: 50; sed: 34; fortran: 5
file content (129 lines) | stat: -rw-r--r-- 3,664 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
(*
  Alpha color values demonstration.

  Copyright (C) 2008 Hazen Babcock
  Copyright (C) 2008, 2010 Hezekiah M. Carty


  This file is part of PLplot.

  PLplot is free software; you can redistribute it and/or modify
  it under the terms of the GNU Library General Public License as published
  by the Free Software Foundation; either version 2 of the License, or
  (at your option) any later version.

  PLplot is distributed in the hope that it will be useful,
  but WITHOUT ANY WARRANTY; without even the implied warranty of
  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
  GNU Library General Public License for more details.

  You should have received a copy of the GNU Library General Public License
  along with PLplot; if not, write to the Free Software
  Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA

  This example will only really be interesting when used with devices that
  support or alpha (or transparency) values, such as the cairo device family.
*)

open Plplot

let red = [|0; 255; 0; 0|]
let green = [|0; 0; 255; 0|]
let blue = [|0; 0; 0; 255|]
let alpha = [|1.0; 1.0; 1.0; 1.0|]

let px = [|0.1; 0.5; 0.5; 0.1|]
let py = [|0.1; 0.1; 0.5; 0.5|]

let pos = [|0.0; 1.0|]
let rcoord = [|1.0; 1.0|]
let gcoord = [|0.0; 0.0|]
let bcoord = [|0.0; 0.0|]
let acoord = [|0.0; 1.0|]
let rev = [|false; false|]

let () =
  plparseopts Sys.argv [PL_PARSE_FULL];

  plinit ();
  plscmap0n 4;
  plscmap0a red green blue alpha;

  (* Page 1:

     This is a series of red, green and blue rectangles overlaid
     on each other with gradually increasing transparency. *)

  (* Set up the window *)
  pladv 0;
  plvpor 0.0 1.0 0.0 1.0;
  plwind 0.0 1.0 0.0 1.0;
  plcol0 0;
  plbox "" 1.0 0 "" 1.0 0;

  (* Draw the boxes *)
  for i = 0 to 8 do
    let icol = i mod 3 + 1 in

    (* Get a color, change its transparency and
       set it as the current color. *)
    let r, g, b, a = plgcol0a icol in
    plscol0a icol r g b (1.0 -. float_of_int i /. 9.0);
    plcol0 icol;

    (* Draw the rectangle *)
    let translate a =
      Array.map (fun x -> x +. 0.5 /. 9.0 *. float_of_int i) a
    in
    plfill (translate px) (translate py);

  done;

  (* Page 2:

     This is a bunch of boxes colored red, green or blue with a single
     large (red) box of linearly varying transparency overlaid. The
     overlaid box is completely transparent at the bottom and completely
     opaque at the top. *)

  (* Set up the window *)
  pladv 0;
  plvpor 0.1 0.9 0.1 0.9;
  plwind 0.0 1.0 0.0 1.0;

  (* Draw the boxes. There are 25 of them drawn on a 5 x 5 grid. *)
  for i = 0 to 4 do
    (* Set box X position *)
    let px0 = 0.05 +. 0.2 *. float_of_int i in
    let px1 = px0 +. 0.1 in
    let px = [|px0; px1; px1; px0|] in

    (* We don't want the boxes to be transparent, so since we changed
       the colors transparencies in the first example we have to change
       the transparencies back to completely opaque. *)
    let icol = i mod 3 + 1 in
    let r, g, b, a = plgcol0a icol in
    plscol0a icol r g b 1.0;
    plcol0 icol;
    for j = 0 to 4 do
      (* Set box y position and draw the box. *)
      let py0 = 0.05 +. 0.2 *. float_of_int j in
      let py2 = py0 +. 0.1 in
      let py = [|py0; py0; py2; py2|] in
      plfill px py;
    done
  done;

  let px = [|0.0; 1.0; 1.0; 0.0|] in
  let py = [|0.0; 0.0; 1.0; 1.0|] in

  (* Create the color map with 128 colors and use plscmap1la to initialize
     the color values with a linear varying transparency (or alpha) *)
  plscmap1n 128;
  plscmap1la true pos rcoord gcoord bcoord acoord (Some rev);

  plgradient px py 90.0;

  plend ();
  ()