~uhh-ssd/+junk/humidity_readout

« back to all changes in this revision

Viewing changes to plplot/plplot-5.9.9/examples/f95/x02f.f90

  • 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
!      $Id: x02f.f90 11680 2011-03-27 17:57:51Z airwin $
 
2
!      Demonstrates multiple windows and color map 0 
 
3
!
 
4
!      Copyright (C) 2004  Alan W. Irwin
 
5
!      Copyright (C) 2005  Andrew Ross
 
6
!
 
7
!      This file is part of PLplot.
 
8
!
 
9
!      PLplot is free software; you can redistribute it and/or modify
 
10
!      it under the terms of the GNU Library General Public License as
 
11
!      published by the Free Software Foundation; either version 2 of the
 
12
!      License, or (at your option) any later version.
 
13
!
 
14
!      PLplot is distributed in the hope that it will be useful,
 
15
!      but WITHOUT ANY WARRANTY; without even the implied warranty of
 
16
!      MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
 
17
!      GNU Library General Public License for more details.
 
18
!
 
19
!      You should have received a copy of the GNU Library General Public
 
20
!      License along with PLplot; if not, write to the Free Software
 
21
!      Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
 
22
 
 
23
      use plplot
 
24
      implicit none
 
25
 
 
26
!      Process command-line arguments
 
27
      call plparseopts(PL_PARSE_FULL)
 
28
 
 
29
 
 
30
!     Initialize plplot
 
31
      call plinit()
 
32
 
 
33
!     Run demos
 
34
      call demo1
 
35
      call demo2
 
36
 
 
37
      call plend
 
38
 
 
39
      end
 
40
 
 
41
 
 
42
!--------------------------------------------------------------------------
 
43
!     demo1
 
44
!
 
45
!     Demonstrates multiple windows and default color map 0 palette.
 
46
!--------------------------------------------------------------------------
 
47
      subroutine demo1
 
48
      use plplot
 
49
      implicit none
 
50
      
 
51
      call plbop
 
52
 
 
53
!     Divide screen into 16 regions
 
54
      call plssub(4,4)
 
55
 
 
56
      call draw_windows(16, 0)
 
57
 
 
58
      call pleop
 
59
 
 
60
      end 
 
61
 
 
62
 
 
63
!--------------------------------------------------------------------------
 
64
!     demo2
 
65
!
 
66
!     Demonstrates multiple windows, user-modified color map 0 palette,
 
67
!     and HLS -> RGB translation. 
 
68
!--------------------------------------------------------------------------
 
69
      subroutine demo2
 
70
      use plplot
 
71
      implicit none
 
72
      integer r(116), g(116), b(116)
 
73
      real(kind=plflt) lmin, lmax
 
74
      parameter (lmin = 0.15_plflt, lmax = 0.85_plflt)
 
75
      integer i
 
76
      real(kind=plflt) h, l, s, r1, g1, b1
 
77
 
 
78
      call plbop
 
79
 
 
80
!     Divide screen into 100 regions
 
81
      call plssub(10,10)
 
82
 
 
83
 
 
84
      do i=0,99
 
85
!     Bounds on HLS, from plhlsrgb() commentary --
 
86
!     hue               [0., 360.]      degrees
 
87
!     lightness         [0., 1.]        magnitude
 
88
!     saturation        [0., 1.]        magnitude
 
89
 
 
90
!     Vary hue uniformly from left to right
 
91
         h = (360._plflt/10._plflt)*mod(i,10)
 
92
!     Vary lightness uniformly from top to bottom, between min and max
 
93
         l = lmin + (lmax - lmin) * (i / 10) / 9._plflt
 
94
!     Use_ max saturation
 
95
         s = 1._plflt
 
96
 
 
97
         call plhlsrgb(h, l, s, r1, g1, b1)
 
98
         
 
99
         r(i+17) = r1*255.001
 
100
         g(i+17) = g1*255.001
 
101
         b(i+17) = b1*255.001
 
102
      enddo
 
103
 
 
104
      do i=1,16
 
105
         call plgcol0(i-1,r(i),g(i),b(i))
 
106
      enddo
 
107
 
 
108
      call plscmap0(r, g, b)
 
109
 
 
110
      call draw_windows(100, 16)
 
111
 
 
112
      call pleop
 
113
 
 
114
      end 
 
115
 
 
116
!--------------------------------------------------------------------------
 
117
!     draw_windows
 
118
!
 
119
!     Draws a set of numbered boxes with colors according to cmap0 entry.
 
120
!--------------------------------------------------------------------------
 
121
      subroutine draw_windows( nw, cmap0_offset )
 
122
      use plplot
 
123
      implicit none
 
124
      integer nw, cmap0_offset
 
125
      integer i,j
 
126
      real(kind=plflt) vmin, vmax
 
127
      character*3 text
 
128
      
 
129
      
 
130
      call plschr(0.0_plflt, 3.5_plflt)
 
131
      call plfont(4)
 
132
 
 
133
      do i=0,nw-1
 
134
        call plcol0(i+cmap0_offset)
 
135
        write (text,'(i3)') i
 
136
        if (i .lt. 10) then
 
137
           text=text(3:3)
 
138
        elseif (i.lt.100) then
 
139
           text=text(2:3)
 
140
        endif
 
141
        call pladv(0)
 
142
        vmin = 0.1_plflt
 
143
        vmax = 0.9_plflt
 
144
        do j=1,3
 
145
          call plwid(j)
 
146
          call plvpor(vmin,vmax,vmin,vmax)
 
147
          call plwind(0.0_plflt, 1.0_plflt, 0.0_plflt, 1.0_plflt)
 
148
          call plbox('bc', 0.0_plflt, 0, 'bc', 0.0_plflt, 0)
 
149
          vmin = vmin + 0.1_plflt
 
150
          vmax = vmax - 0.1_plflt
 
151
        enddo
 
152
        call plwid(1)
 
153
        call plptex(0.5_plflt, 0.5_plflt, 1.0_plflt, 0.0_plflt, 0.5_plflt, text)
 
154
      enddo
 
155
 
 
156
      end