~ubuntu-branches/ubuntu/intrepid/plplot/intrepid

« back to all changes in this revision

Viewing changes to examples/f95/x14f.f90

  • Committer: Bazaar Package Importer
  • Author(s): Rafael Laboissiere
  • Date: 2006-11-04 10:19:34 UTC
  • mfrom: (2.1.8 edgy)
  • Revision ID: james.westby@ubuntu.com-20061104101934-mlirvdg4gpwi6i5q
Tags: 5.6.1-10
* Orphaning the package
* debian/control: Changed the maintainer to the Debian QA Group

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
!      $Id: x14f.f90,v 1.5 2006/05/19 23:28:43 airwin Exp $
 
2
!      Demo of multiple stream/window capability
 
3
!
 
4
!      Copyright (C) 2004  Arjen Markus
 
5
!      Copyright (C) 2004  Alan W. Irwin
 
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 General Library 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
! Plots several simple functions from other example programs.
 
24
!
 
25
! This version sends the output of the first 4 plots (one page) to two
 
26
! independent streams.
 
27
 
 
28
      use plplot
 
29
      implicit none
 
30
 
 
31
      integer i, digmax
 
32
      integer xleng0 , yleng0 , xoff0 , yoff0
 
33
      integer xleng1 , yleng1 , xoff1 , yoff1
 
34
 
 
35
      character*80 driver
 
36
      character*15 geometry_master
 
37
      character*15 geometry_slave
 
38
 
 
39
      real(kind=plflt)  x(101), y(101)
 
40
      real(kind=plflt)  xs(6), ys(6)
 
41
      real(kind=plflt)  xscale, yscale, xoff, yoff
 
42
      common /plotdat/ x, y, xs, ys, xscale, yscale, xoff, yoff
 
43
      character*80 version
 
44
 
 
45
      xleng0 = 400
 
46
      yleng0 = 300
 
47
      xoff0  = 200
 
48
      yoff0  = 200
 
49
      xleng1 = 400
 
50
      xleng1 = 300
 
51
      xoff1  = 500
 
52
      yoff1  = 500
 
53
 
 
54
      geometry_master = '500x410+100+200'
 
55
      geometry_slave = '500x410+650+200'
 
56
 
 
57
!      Process command-line arguments
 
58
      call plparseopts(PL_PARSE_FULL)
 
59
 
 
60
      call plgdev(driver)
 
61
 
 
62
      write(*,*) 'Demo of multiple output streams via the ', &
 
63
        trim(driver), ' driver.'
 
64
      write(*,*) 'Running with the second stream as slave ', &
 
65
        'to the first.'
 
66
      write(*,*)
 
67
 
 
68
!      Set up first stream
 
69
 
 
70
      call plsetopt( 'geometry', geometry_master)
 
71
 
 
72
      call plsdev(driver)
 
73
      call plssub(2, 2)
 
74
      call plinit()
 
75
 
 
76
!      Start next stream
 
77
 
 
78
      call plsstrm(1)
 
79
 
 
80
!      Turn off pause to make this a slave (must follow master)
 
81
 
 
82
      call plsetopt( 'geometry', geometry_slave)
 
83
      call plspause(.false.)
 
84
      call plsdev(driver)
 
85
      call plinit()
 
86
 
 
87
!      Set up the data & plot
 
88
!      Original case
 
89
 
 
90
      call plsstrm(0)
 
91
 
 
92
      xscale = 6._plflt
 
93
      yscale = 1._plflt
 
94
      xoff = 0._plflt
 
95
      yoff = 0._plflt
 
96
      call plot1()
 
97
 
 
98
!      Set up the data & plot
 
99
 
 
100
      xscale = 1._plflt
 
101
      yscale = 1.d+6
 
102
      call plot1()
 
103
 
 
104
!      Set up the data & plot
 
105
 
 
106
      xscale = 1._plflt
 
107
      yscale = 1.d-6
 
108
      digmax = 2
 
109
      call plsyax(digmax, 0)
 
110
      call plot1()
 
111
 
 
112
!      Set up the data & plot
 
113
 
 
114
      xscale = 1._plflt
 
115
      yscale = 0.0014_plflt
 
116
      yoff = 0.0185_plflt
 
117
      digmax = 5
 
118
      call plsyax(digmax, 0)
 
119
      call plot1()
 
120
 
 
121
!      To slave
 
122
!      The pleop() ensures the eop indicator gets lit.
 
123
 
 
124
      call plsstrm(1)
 
125
      call plot4()
 
126
      call pleop()
 
127
 
 
128
!      Back to master
 
129
 
 
130
      call plsstrm(0)
 
131
      call plot2()
 
132
      call plot3()
 
133
 
 
134
!      To slave
 
135
 
 
136
      call plsstrm(1)
 
137
      call plot5()
 
138
      call pleop()
 
139
 
 
140
!      Back to master to wait for user to advance
 
141
 
 
142
      call plsstrm(0)
 
143
      call pleop()
 
144
 
 
145
!      Call plend to finish off.
 
146
 
 
147
      call plend()
 
148
      end
 
149
 
 
150
!======================================================================
 
151
 
 
152
      subroutine plot1()
 
153
      use plplot
 
154
      implicit none
 
155
 
 
156
      real(kind=plflt) x(101), y(101)
 
157
      real(kind=plflt) xs(6), ys(6)
 
158
      real(kind=plflt)  xscale, yscale, xoff, yoff, &
 
159
        xmin, xmax, ymin, ymax
 
160
      integer i
 
161
      common /plotdat/ x, y, xs, ys, xscale, yscale, xoff, yoff
 
162
 
 
163
      do i = 1, 60
 
164
        x(i) = xoff + xscale * dble(i)/60.0_plflt
 
165
        y(i) = yoff + yscale * x(i)**2
 
166
      enddo
 
167
 
 
168
      xmin = x(1)
 
169
      xmax = x(60)
 
170
      ymin = y(1)
 
171
      ymax = y(60)
 
172
 
 
173
      do i = 1, 6
 
174
        xs(i) = x((i-1)*10+4)
 
175
        ys(i) = y((i-1)*10+4)
 
176
      enddo
 
177
 
 
178
!      Set up the viewport and window using PLENV. The range in X is
 
179
!      0.0 to 6.0, and the range in Y is 0.0 to 30.0. The axes are
 
180
!      scaled separately (just = 0), and we just draw a labelled
 
181
!      box (axis = 0).
 
182
 
 
183
      call plcol0(1)
 
184
      call plenv( xmin, xmax, ymin, ymax, 0, 0 )
 
185
      call plcol0(6)
 
186
      call pllab( '(x)', '(y)', '#frPLplot Example 1 - y=x#u2' )
 
187
 
 
188
!      Plot the data points
 
189
 
 
190
      call plcol0(9)
 
191
      call plpoin(xs, ys, 9)
 
192
 
 
193
!      Draw the line through the data
 
194
 
 
195
      call plcol0(4)
 
196
      call plline(x(:60), y(:60))
 
197
      call plflush
 
198
      end
 
199
 
 
200
!======================================================================
 
201
 
 
202
      subroutine plot2()
 
203
      use plplot
 
204
      implicit none
 
205
      real(kind=plflt)  x(101), y(101)
 
206
      real(kind=plflt)  xs(6), ys(6)
 
207
      real(kind=plflt)  xscale, yscale, xoff, yoff
 
208
      integer i
 
209
      common /plotdat/ x, y, xs, ys, xscale, yscale, xoff, yoff
 
210
 
 
211
!======================================================================
 
212
!
 
213
!      Set up the viewport and window using PLENV. The range in X is
 
214
!      -2.0 to 10.0, and the range in Y is -0.4 to 2.0. The axes are
 
215
!      scaled separately (just = 0), and we draw a box with axes
 
216
!      (axis = 1).
 
217
 
 
218
      call plcol0(1)
 
219
      call plenv(-2.0_plflt, 10.0_plflt, -0.4_plflt, 1.2_plflt, 0, 1 )
 
220
      call plcol0(2)
 
221
      call pllab( '(x)', 'sin(x)/x', &
 
222
                  '#frPLplot Example 1 - Sinc Function' )
 
223
 
 
224
!      Fill up the arrays
 
225
 
 
226
      do i = 1, 100
 
227
        x(i) = (i-20.0_plflt)/6.0_plflt
 
228
        y(i) = 1.0_plflt
 
229
        if (x(i) .ne. 0.0_plflt) y(i) = sin(x(i)) / x(i)
 
230
      enddo
 
231
!      Draw the line
 
232
 
 
233
      call plcol0(3)
 
234
      call plline(x(:100), y(:100))
 
235
      call plflush
 
236
      end
 
237
 
 
238
!======================================================================
 
239
 
 
240
      subroutine plot3()
 
241
!
 
242
!      For the final graph we wish to override the default tick intervals,
 
243
!      and so do not use PLENV
 
244
 
 
245
      use plplot, PI => PL_PI
 
246
      implicit none
 
247
      real(kind=plflt)  x(101), y(101)
 
248
      real(kind=plflt)  xs(6), ys(6)
 
249
      real(kind=plflt)  xscale, yscale, xoff, yoff
 
250
      integer i
 
251
      common /plotdat/ x, y, xs, ys, xscale, yscale, xoff, yoff
 
252
      call pladv(0)
 
253
 
 
254
!      Use standard viewport, and define X range from 0 to 360 degrees,
 
255
!      Y range from -1.2 to 1.2.
 
256
 
 
257
      call plvsta()
 
258
      call plwind( 0.0_plflt, 360.0_plflt, -1.2_plflt, 1.2_plflt )
 
259
 
 
260
!      Draw a box with ticks spaced 60 degrees apart in X, and 0.2 in Y.
 
261
 
 
262
      call plcol0(1)
 
263
      call plbox( 'bcnst', 60.0_plflt, 2, 'bcnstv', 0.2_plflt, 2 )
 
264
 
 
265
!      Superimpose a dashed line grid, with 1.5 mm marks and spaces. With
 
266
!      only a single mark and space element, we do not need arrays
 
267
 
 
268
      call plstyl( 1, 1500, 1500 )
 
269
      call plcol0(2)
 
270
      call plbox( 'g', 30.0_plflt, 0, 'g', 0.2_plflt, 0 )
 
271
      call plstyl( 0, 0, 0 )
 
272
 
 
273
      call plcol0(3)
 
274
      call pllab( 'Angle (degrees)', 'sine', &
 
275
                  '#frPLplot Example 1 - Sine function' )
 
276
 
 
277
      do i = 1, 101
 
278
        x(i) = 3.6_plflt * (i-1)
 
279
        y(i) = sin( x(i) * PI/180.0_plflt )
 
280
      enddo
 
281
 
 
282
      call plcol0(4)
 
283
      call plline(x, y)
 
284
      call plflush
 
285
      end
 
286
 
 
287
!======================================================================
 
288
 
 
289
      subroutine plot4()
 
290
 
 
291
      use plplot, PI => PL_PI
 
292
      implicit none
 
293
      character*3 text
 
294
      real(kind=plflt) x0(0:360), y0(0:360)
 
295
      real(kind=plflt) x(0:360), y(0:360), dtr, theta, dx, dy, r
 
296
      integer i, j, nsp
 
297
 
 
298
      dtr = PI/180.0_plflt
 
299
      do i=0,360
 
300
        x0(i) = cos(dtr * dble (i))
 
301
        y0(i) = sin(dtr * dble (i))
 
302
      enddo
 
303
 
 
304
!      Set up viewport and window, but do not draw box
 
305
 
 
306
      call plenv(-1.3_plflt, 1.3_plflt, -1.3_plflt, 1.3_plflt, 1, -2)
 
307
      do i = 1,10
 
308
        do j = 0,360
 
309
          x(j) = 0.1_plflt*i*x0(j)
 
310
          y(j) = 0.1_plflt*i*y0(j)
 
311
        enddo
 
312
 
 
313
!        Draw circles for polar grid
 
314
 
 
315
        call plline(x,y)
 
316
      enddo
 
317
      call plcol0(2)
 
318
      do i = 0,11
 
319
        theta = 30.0_plflt*i
 
320
        dx = cos(dtr*theta)
 
321
        dy = sin(dtr*theta)
 
322
 
 
323
!        Draw radial spokes for polar grid
 
324
 
 
325
        call pljoin(0.0_plflt, 0.0_plflt, dx, dy)
 
326
        write (text,'(i3)') nint(theta)
 
327
 
 
328
!        Write labels for angle
 
329
 
 
330
        text = text(nsp(text):)
 
331
!        Slightly off zero to avoid floating point logic flips at
 
332
!        90 and 270 deg.
 
333
        if (dx.ge.-0.00001_plflt) then
 
334
          call plptex(dx, dy, dx, dy, -0.15_plflt, text)
 
335
        else
 
336
          call plptex(dx, dy, -dx, -dy, 1.15_plflt, text)
 
337
        end if
 
338
      enddo
 
339
!      Draw the graph
 
340
 
 
341
      do i=0,360
 
342
        r = sin(dtr*dble (5*i))
 
343
        x(i) = x0(i) * r
 
344
        y(i) = y0(i) * r
 
345
      enddo
 
346
      call plcol0(3)
 
347
      call plline(x,y)
 
348
 
 
349
      call plcol0(4)
 
350
      call plmtex('t', 2.0_plflt, 0.5_plflt, 0.5_plflt, &
 
351
        '#frPLplot Example 3 - r(#gh)=sin 5#gh')
 
352
 
 
353
!      Flush the plot at end
 
354
 
 
355
      call plflush
 
356
      end
 
357
 
 
358
!======================================================================
 
359
 
 
360
      integer function nsp(text)
 
361
!      ==================
 
362
 
 
363
!      Find first non-space character
 
364
      use plplot
 
365
      implicit none
 
366
 
 
367
      character*(*) text
 
368
      integer l, len
 
369
 
 
370
      l = len(text)
 
371
      nsp = 1
 
372
      do while(text(nsp:nsp).eq.' ' .and. nsp.lt.l)
 
373
        nsp = nsp+1
 
374
      enddo
 
375
      end
 
376
 
 
377
!======================================================================
 
378
 
 
379
      subroutine plot5()
 
380
 
 
381
      use plplot, PI => PL_PI
 
382
      implicit none
 
383
      integer i, j, nptsx, nptsy, xdim, ydim
 
384
!      xdim and ydim are the absolute static dimensions.
 
385
!      nptsx, and nptsy are the (potentially dynamic) defined area of the 2D
 
386
!      arrays that is actually used.
 
387
      parameter (xdim=99, ydim=100, nptsx=35,nptsy=46)
 
388
 
 
389
      real(kind=plflt) z(xdim, ydim), w(xdim, ydim), clevel(11), &
 
390
        xg1(xdim), yg1(ydim), &
 
391
        xg2(xdim, ydim), yg2(xdim, ydim)
 
392
      real(kind=plflt) xx, yy, argx, argy, distort
 
393
      real(kind=plflt) tr(6)
 
394
 
 
395
      data clevel /-1._plflt, -0.8_plflt, -0.6_plflt, -0.4_plflt, &
 
396
        -0.2_plflt, &
 
397
        0._plflt, 0.2_plflt, 0.4_plflt, 0.6_plflt ,0.8_plflt, 1._plflt/
 
398
 
 
399
      tr(1) = 2._plflt/dble(nptsx-1)
 
400
      tr(2) = 0.0_plflt
 
401
      tr(3) = -1.0_plflt
 
402
      tr(4) = 0.0_plflt
 
403
      tr(5) = 2._plflt/dble(nptsy-1)
 
404
      tr(6) = -1.0_plflt
 
405
 
 
406
!      Calculate the data matrices.
 
407
      do i=1,nptsx
 
408
        xx = dble(i-1-(nptsx/2))/dble (nptsx/2)
 
409
        do j=1,nptsy
 
410
          yy = dble(j-1-(nptsy/2))/dble (nptsy/2) - 1.0_plflt
 
411
          z(i,j) = xx*xx - yy*yy
 
412
          w(i,j) = 2._plflt*xx*yy
 
413
        enddo
 
414
      enddo
 
415
 
 
416
!      Build the 1-d coord arrays.
 
417
      distort = 0.4_plflt
 
418
      do i=1,nptsx
 
419
        xx = -1._plflt + dble(i-1)*2._plflt/dble(nptsx-1)
 
420
        xg1(i) = xx + distort*cos(0.5_plflt*PI*xx)
 
421
      enddo
 
422
 
 
423
      do j=1,nptsy
 
424
        yy = -1._plflt + dble(j-1)*2._plflt/dble(nptsy-1)
 
425
        yg1(j) = yy - distort*cos(0.5_plflt*PI*yy)
 
426
      enddo
 
427
 
 
428
!      Build the 2-d coord arrays.
 
429
      do i=1,nptsx
 
430
        xx = -1._plflt + dble(i-1)*2._plflt/dble(nptsx-1)
 
431
        argx = 0.5_plflt*PI*xx
 
432
        do j=1,nptsy
 
433
          yy = -1._plflt + dble(j-1)*2._plflt/dble(nptsy-1)
 
434
          argy = 0.5_plflt*PI*yy
 
435
          xg2(i,j) = xx + distort*cos(argx)*cos(argy)
 
436
          yg2(i,j) = yy - distort*cos(argx)*cos(argy)
 
437
        enddo
 
438
      enddo
 
439
 
 
440
!      Plot using identity transform
 
441
      call plenv(-1.0_plflt, 1.0_plflt, -1.0_plflt, 1.0_plflt, 0, 0)
 
442
      call plcol0(2)
 
443
      call plcont(z,1,nptsx,1,nptsy,clevel,tr)
 
444
      call plstyl(1,1500,1500)
 
445
      call plcol0(3)
 
446
      call plcont(w,1,nptsx,1,nptsy,clevel,tr)
 
447
      call plstyl(0,1500,1500)
 
448
      call plcol0(1)
 
449
      call pllab('X Coordinate', 'Y Coordinate', &
 
450
        'Streamlines of flow')
 
451
 
 
452
      call plflush
 
453
      end