~uhh-ssd/+junk/humidity_readout

« back to all changes in this revision

Viewing changes to plplot/plplot-5.9.9/examples/f95/x25f.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: x25f.f90 11680 2011-03-27 17:57:51Z airwin $
 
2
!
 
3
!   Filling and clipping polygons.
 
4
!
 
5
!   Copyright (C) 2005 Arjen Markus
 
6
!   Copyright (C) 2008 Andrew Ross
 
7
!
 
8
!   This file is part of PLplot.
 
9
!
 
10
!   PLplot is free software; you can redistribute it and/or modify
 
11
!   it under the terms of the GNU Library General Public License as published
 
12
!   by the Free Software Foundation; either version 2 of the License, or
 
13
!   (at your option) any later version.
 
14
!
 
15
!   PLplot is distributed in the hope that it will be useful,
 
16
!   but WITHOUT ANY WARRANTY; without even the implied warranty of
 
17
!   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
 
18
!   GNU Library General Public License for more details.
 
19
!
 
20
!   You should have received a copy of the GNU Library General Public License
 
21
!   along with PLplot; if not, write to the Free Software
 
22
!   Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
 
23
!
 
24
!
 
25
! --------------------------------------------------------------------------
 
26
! main
 
27
!
 
28
! Test program for filling polygons and proper clipping
 
29
! --------------------------------------------------------------------------
 
30
 
 
31
program x25f
 
32
 
 
33
  use plplot
 
34
  implicit none
 
35
 
 
36
  integer i, j, k
 
37
  integer npts
 
38
  real(kind=plflt) xextreme(2,10)
 
39
  real(kind=plflt) yextreme(2,10)
 
40
  real(kind=plflt) x0(10)
 
41
  real(kind=plflt) y0(10)
 
42
 
 
43
  data ( xextreme(1,i), xextreme(2,i), yextreme(1,i), yextreme(2,i), &
 
44
       i=1,9) / &
 
45
       -120.0_plflt,      120.0_plflt,     -120.0_plflt,      120.0_plflt, &
 
46
       -120.0_plflt,      120.0_plflt,       20.0_plflt,      120.0_plflt, &
 
47
       -120.0_plflt,      120.0_plflt,      -20.0_plflt,      120.0_plflt, &
 
48
       -80.0_plflt,       80.0_plflt,      -20.0_plflt,      120.0_plflt, &
 
49
       -220.0_plflt,     -120.0_plflt,     -120.0_plflt,      120.0_plflt, &
 
50
       -20.0_plflt,       20.0_plflt,     -120.0_plflt,      120.0_plflt, &
 
51
       -20.0_plflt,       20.0_plflt,      -20.0_plflt,       20.0_plflt, &
 
52
       -80.0_plflt,       80.0_plflt,      -80.0_plflt,       80.0_plflt, &
 
53
       20.0_plflt,      120.0_plflt,     -120.0_plflt,      120.0_plflt/ 
 
54
 
 
55
  npts = 0
 
56
 
 
57
  !  Parse and process command line arguments
 
58
 
 
59
  call plparseopts(PL_PARSE_FULL)
 
60
 
 
61
  !  Initialize plplot
 
62
 
 
63
  call plssub(3,3)
 
64
  call plinit()
 
65
 
 
66
  do k = 1,2
 
67
     do j = 1,4
 
68
 
 
69
        if ( j .eq. 1 ) then
 
70
           !  Polygon 1: a diamond
 
71
           x0(1) =    0.0_plflt
 
72
           y0(1) = -100.0_plflt
 
73
           x0(2) = -100.0_plflt
 
74
           y0(2) =    0.0_plflt
 
75
           x0(3) =    0.0_plflt
 
76
           y0(3) =  100.0_plflt
 
77
           x0(4) =  100.0_plflt
 
78
           y0(4) =    0.0_plflt
 
79
           npts = 4
 
80
        endif
 
81
        if ( j .eq. 2 ) then
 
82
           !  Polygon 1: a diamond - reverse direction
 
83
           x0(4) =    0.0_plflt
 
84
           y0(4) = -100.0_plflt
 
85
           x0(3) = -100.0_plflt
 
86
           y0(3) =    0.0_plflt
 
87
           x0(2) =    0.0_plflt
 
88
           y0(2) =  100.0_plflt
 
89
           x0(1) =  100.0_plflt
 
90
           y0(1) =    0.0_plflt
 
91
           npts = 4
 
92
        endif
 
93
        if ( j .eq. 3 ) then
 
94
           !  Polygon 2: a square with punctures
 
95
           x0(1)  = -100.0_plflt
 
96
           y0(1)  = -100.0_plflt
 
97
           x0(2)  = -100.0_plflt 
 
98
           y0(2)  =  -80.0_plflt
 
99
           x0(3)  =   80.0_plflt
 
100
           y0(3)  =    0.0_plflt
 
101
           x0(4)  = -100.0_plflt
 
102
           y0(4)  =   80.0_plflt
 
103
           x0(5)  = -100.0_plflt
 
104
           y0(5)  =  100.0_plflt
 
105
           x0(6)  =  -80.0_plflt
 
106
           y0(6)  =  100.0_plflt
 
107
           x0(7)  =    0.0_plflt
 
108
           y0(7)  =   80.0_plflt
 
109
           x0(8)  =   80.0_plflt
 
110
           y0(8)  =  100.0_plflt
 
111
           x0(9)  =  100.0_plflt
 
112
           y0(9)  =  100.0_plflt
 
113
           x0(10) =  100.0_plflt
 
114
           y0(10) = -100.0_plflt
 
115
           npts = 10
 
116
        endif
 
117
        if ( j .eq. 4 ) then
 
118
           !  Polygon 2: a square with punctures - reversed direction 
 
119
           x0(10) = -100.0_plflt
 
120
           y0(10) = -100.0_plflt
 
121
           x0(9)  = -100.0_plflt
 
122
           y0(9)  =  -80.0_plflt
 
123
           x0(8)  =   80.0_plflt
 
124
           y0(8)  =    0.0_plflt
 
125
           x0(7)  = -100.0_plflt
 
126
           y0(7)  =   80.0_plflt
 
127
           x0(6)  = -100.0_plflt
 
128
           y0(6)  =  100.0_plflt
 
129
           x0(5)  =  -80.0_plflt
 
130
           y0(5)  =  100.0_plflt
 
131
           x0(4)  =    0.0_plflt
 
132
           y0(4)  =   80.0_plflt
 
133
           x0(3)  =   80.0_plflt
 
134
           y0(3)  =  100.0_plflt
 
135
           x0(2)  =  100.0_plflt
 
136
           y0(2)  =  100.0_plflt
 
137
           x0(1)  =  100.0_plflt
 
138
           y0(1)  = -100.0_plflt
 
139
           npts = 10
 
140
        endif
 
141
 
 
142
        do i = 1,9
 
143
           call pladv(0)
 
144
           call plvsta()
 
145
           call plwind(xextreme(1,i), xextreme(2,i), &
 
146
                yextreme(1,i), yextreme(2,i))
 
147
 
 
148
           call plcol0(2)
 
149
           call plbox('bc', 1.0d0, 0, 'bcnv', 10.0d0, 0)
 
150
           call plcol0(1)
 
151
           call plpsty(0)
 
152
           if(k.eq.1) then
 
153
              call plfill(x0(1:npts),y0(1:npts))
 
154
           else
 
155
              call plgradient(x0(1:npts),y0(1:npts),45.d0)
 
156
           endif
 
157
           call plcol0(2)
 
158
           call pllsty(1)
 
159
           call plline(x0(1:npts),y0(1:npts))
 
160
        end do
 
161
     end do
 
162
  end do
 
163
  !  Don't forget to call plend() to finish off!
 
164
 
 
165
  call plend()
 
166
 
 
167
end program x25f