source: PSPA/madxPSPA/src/gxx11ps.f90 @ 478

Last change on this file since 478 was 430, checked in by touze, 11 years ago

import madx-5.01.00

File size: 193.1 KB
Line 
1subroutine gvfa(np, x, y)
2  use gxx11_common
3  implicit none
4  integer i,icol,ierr,np
5  real fx,fy,xs,ys
6  !***********************************************************************
7  !
8  !   Purpose: Fill area plot with viewport emulation for HIGZ
9  !
10  !--- Input
11  !    NP, x, y: as for GFA
12  !   Author: H. Grote / CERN                        date: Nov. 30, 1993
13  !                                              last mod: Nov. 30, 1993
14  !***********************************************************************
15  real x(*), y(*)
16
17  real w(4), v(4)
18
19  !--- set proper colour index
20  call jqlctp(i)
21  if (i .ne. 2)  then
22     call jslctp(2)
23     call jqplci(ierr, icol)
24     call gxscol(icol)
25  endif
26  !--- open .eps file if requested
27  if (iepsop .lt. 0) call gxstep
28  !--- get current window
29  call jqnt(1, ierr, w, v)
30  !--- transform
31  xs = w(2) - w(1)
32  fx = vpfacx / xs
33  ys = w(4) - w(3)
34  fy = vpfacy / ys
35  do  i = 1, np
36     xvp(i) = w(1) + xs * (vploc(1) + fx * (x(i) - w(1)))
37     yvp(i) = w(3) + ys * (vploc(3) + fy * (y(i) - w(3)))
38  enddo
39  call gfa(np, xvp, yvp)
40  !--- set flag for clear permission
41  iclear = 1
42end subroutine gvfa
43subroutine gvpl(np, x, y)
44  use gxx11_common
45  implicit none
46  integer i,icol,ierr,iloop,ilow,n,np,nup
47  real fx,fy,xs,ys
48  !***********************************************************************
49  !
50  !   Purpose: Plot polyline and emulate viewports for HIGZ or X11
51  !
52  !--- Input
53  !   np, x, y: as for GPL
54  !   Author: H. Grote / CERN                        date: Nov. 18, 1992
55  !                                           last mod: May 13, 1993
56  !***********************************************************************
57  real x(*), y(*)
58
59  real w(4), v(4)
60  !--- set proper colour index
61  call jqlctp(i)
62  if (i .ne. 2)  then
63     call jslctp(2)
64     call jqplci(ierr, icol)
65     call gxscol(icol)
66  endif
67  !--- open .eps file if requested
68  if (iepsop .lt. 0) call gxstep
69  !--- get current window
70  call jqnt(1, ierr, w, v)
71  !--- transform
72  xs = w(2) - w(1)
73  fx = vpfacx / xs
74  ys = w(4) - w(3)
75  fy = vpfacy / ys
76  do  iloop=1, np, madim2
77     nup = min(np, iloop + madim2 - 1)
78     ilow = max(1, iloop - 1)
79     n = 0
80     do  i = ilow, nup
81        n = n + 1
82        xvp(n) = w(1) + xs * (vploc(1) + fx * (x(i) - w(1)))
83        yvp(n) = w(3) + ys * (vploc(3) + fy * (y(i) - w(3)))
84     enddo
85     call gpl(n, xvp, yvp)
86  enddo
87  !--- set flag for clear permission
88  iclear = 1
89end subroutine gvpl
90subroutine gvpm(np, x, y)
91  use gxx11_common
92  implicit none
93  integer i,icol,ierr,iloop,n,np,nup
94  real fx,fy,xs,ys
95  !***********************************************************************
96  !
97  !   Purpose: Plot marker symbol and emulate viewports for HIGZ or X11
98  !
99  !--- Input
100  !   np, x, y: as for GPM
101  !   Author: H. Grote / CERN                        date: Nov. 18, 1992
102  !                                           last mod: May 13, 1993
103  !***********************************************************************
104  real x(*), y(*)
105
106  real w(4), v(4)
107
108  !--- set proper colour index
109  call jqlctp(i)
110  if (i .ne. 2)  then
111     call jslctp(2)
112     call jqpmci(ierr, icol)
113     call gxscol(icol)
114  endif
115  !--- open .eps file if requested
116  if (iepsop .lt. 0) call gxstep
117  !--- get current window
118  call jqnt(1, ierr, w, v)
119  !--- transform
120  xs = w(2) - w(1)
121  fx = vpfacx / xs
122  ys = w(4) - w(3)
123  fy = vpfacy / ys
124  do  iloop=1, np, madim2
125     nup = min(np, iloop + madim2 - 1)
126     n = 0
127     do  i = iloop, nup
128        n = n + 1
129        xvp(n) = w(1) + xs * (vploc(1) + fx * (x(i) - w(1)))
130        yvp(n) = w(3) + ys * (vploc(3) + fy * (y(i) - w(3)))
131     enddo
132     call gxwpm(n, xvp, yvp)
133  enddo
134  !--- set flag for clear permission
135  iclear = 1
136end subroutine gvpm
137subroutine gvtx(x, y, sss)
138  use gxx11_common
139  implicit none
140  integer i,icol,ierr
141  real chh,chux,chuy,fx,fy,hfac,x,xs,y,ys
142  !***********************************************************************
143  !
144  !   Purpose: Plot text and emulate viewports for HIGZ or X11
145  !
146  !--- Input
147  !   x, y, s: as for GTX
148  !   Author: H. Grote / CERN                        date: Nov. 18, 1992
149  !                                           last mod: May 13, 1993
150  !***********************************************************************
151  character(*) sss
152
153  real w(4), v(4)
154
155  !--- set proper colour index
156  call jqlctp(i)
157  if (i .ne. 2)  then
158     call jslctp(2)
159     call jqtxci(ierr, icol)
160     call gxscol(icol)
161  endif
162  !--- open .eps file if requested
163  if (iepsop .lt. 0) call gxstep
164  !--- get current window
165  call jqnt(1, ierr, w, v)
166  !--- get current character height and text orientation
167  call jqchh(ierr, chh)
168  call jqchup(ierr, chux, chuy)
169  !--- transform
170  xs = w(2) - w(1)
171  fx = vpfacx / xs
172  ys = w(4) - w(3)
173  fy = vpfacy / ys
174  if (chux .eq. 0.)  then
175     hfac = fy
176  else
177     hfac = fx
178  endif
179  call jschh(hfac * chh)
180  xvp(1) = w(1) + xs * (vploc(1) + fx * (x - w(1)))
181  yvp(1) = w(3) + ys * (vploc(3) + fy * (y - w(3)))
182  call gtx(xvp(1), yvp(1), sss)
183  call jschh(chh)
184  !--- set flag for clear permission
185  iclear = 1
186end subroutine gvtx
187subroutine gxarng(nopt,rmini,rmaxi,rmin,rmax,nint)
188  implicit none
189  integer nint,nopt
190  real rmax,rmaxi,rmin,rmini
191  !***********************************************************************
192  !
193  !   Purpose: calculates axis ranges
194  !
195  !--- Input
196  !   nopt         =0: normal
197  !              =1: start or terminate axis at 0. if possible
198  !              =2: centre axis around 0.
199  !   rmini        minimum (x or y) value to consider
200  !   rmaxi        maximum (x or y) value to consider
201  !--- Output
202  !   rmin         lower end of axis
203  !   rmax         upper end of axis
204  !   nint         no. of intervals as returned by GXSCAL
205  !
206  !   Author: H. Grote / CERN                        date: June 16, 1987
207  !                                           last mod: Aug. 8, 1988
208  !
209  !***********************************************************************
210  nint=10
211  if(rmini.ge.rmaxi) then
212     rmin=rmini
213     rmax=rmini+1.
214  else
215     if(nopt.eq.0) then
216        call gxscal(rmini,rmaxi,rmin,rmax,nint)
217     elseif(nopt.eq.1) then
218        !--- start or terminate at 0.
219        if(rmini.gt.0.) then
220           call gxscal(0.,rmaxi,rmin,rmax,nint)
221        elseif(rmaxi.lt.0.) then
222           call gxscal(0.,-rmini,rmin,rmax,nint)
223           rmin=-rmax
224           rmax=0.
225        else
226           call gxscal(rmini,rmaxi,rmin,rmax,nint)
227        endif
228     else
229        call gxscal(0.,max(abs(rmini),abs(rmaxi)),rmin,rmax,nint)
230        rmin=-rmax
231     endif
232  endif
233end subroutine gxarng
234subroutine gxasku
235  use gxx11_common
236  implicit none
237  !***********************************************************************
238  !
239  !   Purpose: asks user interactively for plot options
240  !
241  !   must be called before GXINIT if at all
242  !
243  !   Author: H. Grote / CERN                        date: June 16, 1987
244  !                                           last mod: May 13, 1993
245  !
246  !***********************************************************************
247  logical intrac
248
249  call gxundf
250  if (intrac())  then
251     call gxask1
252     call gxask2
253  endif
254end subroutine gxasku
255subroutine gxask1
256  use gxx11_common
257  implicit none
258  !***********************************************************************
259  !
260  !   Purpose: asks user interactively plot window
261  !
262  !   called by GXASKU
263  !
264  !   Author: H. Grote / CERN                        date: May 13, 1993
265  !                                           last mod: May 13, 1993
266  !
267  !***********************************************************************
268
269  !--- Input and Output unit definition
270  if(lnunit.ne.lundef)  call gxsvar('INUNIT',miunit,0.,' ')
271  if(lounit.ne.lundef)  call gxsvar('IOUNIT',mounit,0.,' ')
272  itermt=0
273  interm=0
274  lnterm=lundef
275  ltermt=lundef
276  goto 999
27730 continue
278  write(iounit,*) ' Error on Input, stop.'
279  stop
28010000 format(//' GX (X11 based) plot package initialization'/)
28110010 format(/' Do you want to plot on your terminal ? (<CR> = yes>:'/)
282999 end subroutine gxask1
283subroutine gxask2
284  use gxx11_common
285  implicit none
286  integer iamx,iamy,ierr,ifirst,ilast
287  real xax,yax
288  !***********************************************************************
289  !
290  !   Purpose: asks user interactively for Postscript file
291  !
292  !   called by GXASKU
293  !
294  !   Author: H. Grote / CERN                        date: May 13, 1993
295  !                                           last mod: May 13, 1993
296  !
297  !***********************************************************************
298  character sline*80
299  character(60) gxform, sform
300  logical affirm
301
302  if (lpseps .ne. lundef)  then
303     write(iounit,10040)
304     call gxrdtx(inunit,sline,ierr)
305     if(ierr.ne.0) goto 30
306     call gxpnbl(sline, ifirst, ilast)
307     if(ifirst .eq. 0)  then
308        ipseps = 0
309     elseif (index('0123456789', sline(:ifirst)) .eq. 0)  then
310        ipseps = 0
311     else
312        sform = '(I$$)'
313        write (sform(3:4), '(I2.2)')  ilast
314        read (sline, sform) ipseps
315        if (ipseps .ge. 1 .and. ipseps .le. 2)  then
316           call jswks(1)
317           inmeta = mtmeta
318           if(lmetop .ne. lundef)  then
319              if (lmetnm .ne. lundef)  then
320                 smetnm = 'gxx11'
321                 call gxpnbl(smetnm, ifirst, ilast)
322                 write(iounit,10100) smetnm(ifirst:ilast),               &
323                      smetnm(ifirst:ilast)
324                 call gxrdtx(inunit,sline,ierr)
325                 if(sline(1:1).ne.' ')                                   &
326                      call gxsvar('SMETNM',0,0.,sline)
327                 lmetnm = lundef
328              endif
329           endif
330        else
331           ipseps = 0
332        endif
333     endif
334  endif
335  lpseps = lundef
336  lnmeta=lundef
337  if (ipseps .eq. 0)  then
338     inmeta = 0
339  else
340     inmeta = mtmeta
341     !--- paper size (only if not set already)
342     if(lmetax.ne.lundef.or.lmetay.ne.lundef)  then
343        iamx = mxsize
344        iamy = mysize
345        xax = iamx
346        yax = iamy
347        write(iounit,10050) iamx, iamy
348        call gxrdtx(inunit,sline,ierr)
349        if(ierr.ne.0) goto 30
350        if(affirm(sline(1:1))) then
351           write(iounit,10070)
352           call gxrdtx(inunit,sline,ierr)
353           if(ierr.ne.0) goto 30
354           sform=gxform(sline)
355           if(index(sform,'I').ne.0)  then
356              read(sline,sform)  iamx
357              xax = iamx
358           else
359              read(sline,sform) xax
360           endif
361           write(iounit,10080)
362           call gxrdtx(inunit,sline,ierr)
363           if(ierr.ne.0) goto 30
364           sform=gxform(sline)
365           if(index(sform,'I').ne.0)  then
366              read(sline,sform)  iamy
367              yax = iamy
368           else
369              read(sline,sform) yax
370           endif
371        endif
372        call gxsvar('XMETAF', 0, xax, ' ')
373        call gxsvar('YMETAF', 0, yax, ' ')
374     endif
375  endif
376  goto 999
37730 continue
378  write(iounit,*) ' Error on Input, stop.'
379  stop
38010040 format(/' Do you want to write a .ps file <1>, .eps files <2>,',  &
381       ' or none <CR>:'/)
38210050 format                                                            &
383       (/' specify bounding box size (default:',i3,                      &
384       '(x) by', i3, '(y) cm)?'/' (<CR>=no):'/)
38510070 format(/' enter bounding box x size in cm:'/)
38610080 format(/' enter bounding box y size in cm:'/)
38710100 format(/' enter postscript or eps file name (leading part)' /     &
388       ' (<CR> gives "',a,'.ps" resp. "',a,'nn.eps"):'/)
389999 end subroutine gxask2
390subroutine gxaxis(type,axlow,axup,axpos,ipos,fmt,textin,sepchr,iparm,ierr)
391  implicit none
392  integer i,ia,ialow,iaup,iaxort,ie,ierr,ietick,ifircl,ifirst,ifont,&
393       ifs,ilabl,ilast,ilbort,ils,impfl,in,intrep,intv,ipos,irf,iscloc,  &
394       islbl,islpc,isp,ispchl,isradc,itext,itick,ival,k1,k2,l,l1,l2,     &
395       naxal,nchct,nlines
396  real a1,a1b,a2,alp,amxx,axlow,axpos,axup,chhigh,chwdth,cthigh,    &
397       cuhigh,diff,diffe,diffn,fcw,fwc,hxf,pfact,ptick,sgspac,sk,space,  &
398       sphlin,spmlog,spwlin,spwlog,tickl,wbused,wsused
399  !***********************************************************************
400  !
401  !   Purpose: plots an axis with tick marks, numbers, and title
402  !
403  !-- Input
404  !   type        'X' for an x-axis, 'Y' for a y-axis
405  !   axlow       lower end of axis in current world coords.
406  !   axup        upper end of axis in current world coords.
407  !   axpos       position of axis in the other coordinate
408  !   ipos        =0: AXPOS value given in normalized dev. coord. [0.,1.]
409  !            =1: AXPOS value given in current world coords.
410  !   fmt         (floating point) format for axis labels (=numbers)
411  !            including the brackets, e.g. '(F6.3)'. If blank,
412  !            a reasonable default is used.
413  !   textin      axis title (trailing blanks will be suppressed)
414  !   sepchr      will start a new line when encountered in TEXT
415  !   iparm       axis parameters:
416  !   1        0 = linear scaling
417  !         1 = logarithmic scale
418  !+++ if the user scale makes no sense, scaling is switched to automatic
419  !
420  !   2        if = 0, no tick marks. If < 0, the number of intervals
421  !         will be chosen automatically.
422  !         if linear scaling and > 0, no. of major tick mark intervals
423  !         (labels are only written at major tick marks).
424  !         if log. scaling and <> 0, major tick marks at the powers of
425  !         ten in the scale, i.e. at all integer values.
426  !
427  !   3        0 no labels (scale numbers), 1 hor. labels, 2 vertical
428  !
429  !   4        odd for tick mark below (x-axis) or at left (y axis),
430  !         even for above resp. at right.
431  !         if = 0, no ticks
432  !
433  !   5        as 4, but for labels (=scale numbers)
434  !
435  !   6        as 4, but for the axis text (title)
436  !         the text is written horizontally for x-, vertically for y-axes
437  !
438  !   7        character height in normalized pixels
439  !
440  !   8        tick mark length in normalized pixels
441  !         a normalized pixel is defined as follows: imagine your
442  !         default (square) screen (device) area devided into
443  !         1000 x 1000 pixels, i.e. one pixel is 0.001 x 0.001 in NDC
444  !
445  !   9        Linear scaling: no. of extra intervals with half-size ticks
446  !         between main ticks
447  !         log. scaling: if > 0 : flag that extra ticks are to be
448  !         plotted at the positions log(2), log(3),..., log(9)
449  !
450  !   10       =1 : adjust axis titles at left, =2 centre, =3 adjust
451  !         them at right. If the string '<#>' is found inside a line,
452  !         the text to the left of it will always be left adjusted,
453  !         the text to the right of it right adjusted.
454  !
455  !   11       text font for axis labels, default = 1 (see GKS for details)
456  !
457  !   12       if 0 (default) no minor labels at minor ticks
458  !         for log. scale, if > 0 yes
459  !
460  !   13       if > 0 and not > 1000: character height for axis text, else
461  !         parameter 7 is used
462  !
463  !-- Output
464  !   ierr        =0: everything OK
465  !            =-1: AXLOW.GE.AXUP
466  !            else the corresponding GKS error
467  !
468  !   Author: H. Grote / CERN                        date: June 16, 1987
469  !                                           last mod: Feb. 3, 1993
470  !
471  !***********************************************************************
472  character(*)  textin,fmt,type,sepchr
473  integer iparm(*)
474  character   stext*240,text*240,sltext*40,                         &
475       fmtloc*60,stsep*1,slog(9)*1
476  integer isave(20),ihoral(2,2,2),iveral(2,2,2)
477  real atext(4),tick(4),alabl(4),cnt(4),rsave(20),tetick(4),        &
478       alogv(10)
479  logical xaxis,linscl, labflg
480  save alogv, ifircl, ihoral, iveral, slog
481  !--- horizontal and vertical alignment as function of orientation (I),
482  !   position above or below etc. (J) and axis (x or y) (K), e.g.
483  !   iveral(1,2,1) vertical alignment for horizontal labels above an x axis
484  data ihoral/2,3,2,1,3,2,1,2/
485  data iveral/1,3,5,3,3,5,3,1/
486  data slog/'1','2','3','4','5','6','7','8','9'/
487  data ifircl/0/
488  stext = ' '
489  text = ' '
490  sltext = ' '
491  fmtloc = ' '
492  stsep = ' '
493  do i = 1, 20
494     isave(i) = 0
495  enddo
496  do i = 1, 9
497     slog(i) = ' '
498  enddo
499  do i=1,4
500     atext(i)=0.
501  enddo
502  do i=1,20
503     rsave(i)=0.
504  enddo
505  space=0.
506  if(ifircl.eq.0)  then
507     !--- set logarithms
508     do i=1,10
509        alogv(i)=log10(float(i))
510     enddo
511     ifircl=1
512  endif
513  !
514  !--- check for reasonable axis range
515  !
516  if(axlow.ge.axup)  then
517     ierr=-1
518     goto 999
519  endif
520  !
521  !--- get current user settings and keep them
522  call gxsave(isave,rsave,ierr)
523  if(ierr.ne.0) goto 999
524  !
525  !--- get Input parameters
526  !
527  stsep=sepchr
528  xaxis=type(:1).eq.'X'
529  if(xaxis)  then
530     iaxort=1
531  else
532     iaxort=2
533  endif
534  linscl=iparm(1).eq.0
535  intv=iparm(2)
536  if(intv.lt.0)  then
537     !--- choose number of intervals automatically if linear
538     if(linscl)  then
539        call gxdint(axlow,axup,intv)
540     else
541        intv=1
542     endif
543  endif
544  labflg = .false.
545  fmtloc=fmt
546  call gxival(fmtloc,ival)
547  if(ival.eq.0 .and. linscl)  then
548     !--- use reasonable default as format
549     call gxdfmt(axlow,axup,intv,ival,iscloc,fmtloc)
550  else
551     iscloc = 0
552  endif
553  ilbort=iparm(3)
554  if(ilbort.gt.0)  ilbort=mod(ilbort-1,2)+1
555  itick=iparm(4)
556  ietick=iparm(9)
557  if(itick.gt.0)  itick=mod(itick-1,2)+1
558  ilabl=iparm(5)
559  if(ilabl.gt.0)  ilabl=mod(ilabl-1,2)+1
560  itext=iparm(6)
561  if(itext.gt.0)  itext=mod(itext-1,2)+1
562  cuhigh=.001*iparm(7)
563  if(iparm(13).gt.0.and.iparm(13).le.1000)  then
564     cthigh=.001*iparm(13)
565  else
566     cthigh=cuhigh
567  endif
568  tickl =.001*iparm(8)
569  if(itick.eq.0)  tickl=0.
570  naxal=iparm(10)
571  ifont=iparm(11)
572  islpc=iparm(12)
573  if(xaxis)  then
574     k1=1
575     k2=3
576  else
577     k1=3
578     k2=1
579     !--- apply expansion factor to tick marks if y axis
580     call gxqrvp(hxf)
581     tickl=hxf*tickl
582  endif
583  !
584  !--- transform into normalized window
585  !
586  if(isave(1).ne.0)  then
587     !--- rsave(1...4) contains the window
588     !   fwc converts a length along the axis from world to NDC
589     !   fcw does the inverse of FWC
590     fcw=(rsave(k1+1)-rsave(k1))
591     fwc=1./fcw
592     cnt(k1)=fwc*(axlow-rsave(k1))
593     cnt(k1+1)=fwc*(axup-rsave(k1))
594     if(ipos.gt.0)  then
595        cnt(k2)=(axpos-rsave(k2))/(rsave(k2+1)-rsave(k2))
596     else
597        cnt(k2)=axpos
598     endif
599     call jswn(isave(1),0.,1.,0.,1.)
600     !     call jselnt(isave(1))
601  else
602     fcw=1.
603     fwc=1.
604     cnt(k1)=axlow
605     cnt(k1+1)=axup
606     cnt(k2)=axpos
607  endif
608  cnt(k2+1)=cnt(k2)
609  !
610  !--- set line style
611  !
612  call gxspmt
613  !
614  !   set font and precision
615  !
616  call jstxfp(ifont,2)
617  !
618  !--- plot a line for the axis
619  !
620  call gvpl(2,cnt(1),cnt(3))
621  !
622  !--- plot tick marks, labels, and title
623  !
624  tick(k2)=cnt(k2)
625  tick(k2+1)=cnt(k2+1)
626  tetick(k2)=cnt(k2)
627  tetick(k2+1)=cnt(k2+1)
628  alabl(k2)=cnt(k2)
629  alabl(k2+1)=cnt(k2+1)
630  if(intv.gt.0)  then
631     if(itick.eq.2) then
632        !--- plot tick marks above x-axis, or to the right of y-axis
633        tick(k2+1)=cnt(k2)+tickl
634        tetick(k2+1)=cnt(k2)+.5*tickl
635     else
636        tick(k2+1)=cnt(k2)-tickl
637        tetick(k2+1)=cnt(k2)-.5*tickl
638     endif
639     if(linscl)  then
640        diff=(axup-axlow)/intv
641        diffn=(cnt(k1+1)-cnt(k1))/intv
642        diffe=diffn/max(ietick,1)
643        if(tickl.gt.0.) then
644           do i=0,intv
645              !--- tick marks
646              tick(k1)=cnt(k1)+diffn*i
647              tick(k1+1)=tick(k1)
648              call gvpl(2,tick(1),tick(3))
649              !--- extra ticks
650              if(i.lt.intv) then
651                 do ie=1,ietick-1
652                    tetick(k1)=tick(k1)+ie*diffe
653                    tetick(k1+1)=tetick(k1)
654                    call gvpl(2,tetick(1),tetick(3))
655                 enddo
656              endif
657           enddo
658        endif
659     elseif(tickl.gt.0.) then
660        !--- log scale
661        ialow=axlow
662        if(axlow.lt.float(ialow))  ialow=ialow-1
663        ialow=sign(min(abs(ialow),99),ialow)
664        iaup=axup
665        if(axup.lt.float(iaup))  iaup=iaup-1
666        iaup=sign(min(abs(iaup),99),iaup)
667        ia=ialow
668        !--- start loop
66940      continue
670        do i=1,9
671           alp=ia+alogv(i)
672           if(alp.gt.axup) goto 60
673           if(alp.ge.axlow) then
674              if(i.eq.1.or.ietick.ne.0)  then
675                 tick(k1)=(alp-rsave(k1))*fwc
676                 tick(k1+1)=tick(k1)
677                 call gvpl(2,tick(1),tick(3))
678              endif
679           endif
680        enddo
681        ia=ia+1
682        goto 40
683        !--- end loop
68460      continue
685     endif
686     !--- labels
687     if(ilbort.eq.0.or.ilabl.eq.0.or.cuhigh.eq.0.) then
688        alabl(k2)=tick(k2)
689        alabl(k2+1)=alabl(k2)
690     else
691        labflg = .true.
692        !--- set correct character height (viewports !), get width
693        call gxschf(1,ilbort,cuhigh,chhigh,chwdth)
694        space=.5*chhigh
695        if(iaxort.eq.ilbort) then
696           sphlin=chhigh
697           spwlin=chwdth*ival
698           spwlog=2.5*chwdth
699           spmlog=chwdth
700        else
701           spwlin=chhigh
702           sphlin=chwdth*ival
703           spwlog=chhigh
704           spmlog=chhigh
705        endif
706        if(ilabl.eq.2) then
707           !--- plot labels above x-axis, or to the right of y-axis
708           alabl(k2)=max(tick(k2),tick(k2+1))+space
709           alabl(k2+1)=alabl(k2)+sphlin
710        else
711           alabl(k2)=min(tick(k2),tick(k2+1))-space
712           alabl(k2+1)=alabl(k2)-sphlin
713        endif
714        !--- set text alignment
715        call jstxal(ihoral(ilbort,ilabl,iaxort),                      &
716             iveral(ilbort,ilabl,iaxort))
717        if(linscl)  then
718           !--- linear scale
719           intrep=spwlin/diffn+.99999
720           amxx=max(abs(axlow),abs(axup))
721           pfact = 10.**(-iscloc)
722           do i=0,intv,intrep
723              !--- centered figures
724              ptick=axlow+diff*i
725              alabl(k1)=cnt(k1)+diffn*i
726              if(abs(ptick)/amxx.lt.1.e-5)  then
727                 sltext='0.0'
728              else
729                 write(sltext,fmtloc) pfact * ptick
730              endif
731              call gxpnbl(sltext,ifirst,ilast)
732              call gxstx(alabl(1),alabl(3),sltext(ifirst:ilast))
733           enddo
734        else
735           !---  log scale
736           !   impfl = 0 if power of ten to be plotted with first minor label,
737           !   else > 0
738           impfl=iaup-ialow
739           !--- islbl = 0 if no secondary label to be plotted else 1
740           if(ietick.eq.0.or.islpc.eq.0)  then
741              islbl=0
742           else
743              islbl=1
744           endif
745           !--- wbused = half space used by major label in WC
746           wbused=spwlog*fcw
747           !--- wsused = half space used by minor label in WC
748           wsused=2.*spmlog*fcw
749           ia=ialow
750           !--- interval which is free for major labels
751           a1b=ialow-1000.
752           !--- start loop
75380         continue
754           !--- interval which is free for minor labels
755           a1=ia+wbused
756           a2=ia+1.-wbused
757           do i=1,9
758              !--- label position in WC
759              alp=ia+alogv(i)
760              if(alp.gt.axup) goto 100
761              if(alp.ge.axlow)  then
762                 !--- label position in NDC
763                 alabl(k1)=(alp-rsave(k1))*fwc
764                 if(i.eq.1.and.alp.ge.a1b+wbused) then
765                    !--- major label (at integers)
766                    call gxppow(alabl,ia)
767                    a1b=alp+wbused
768                 else
769                    if(islbl.ne.0.and.alp.ge.a1+wsused .and.alp.le.       &
770                         a2-wsused) then
771                       !--- minor label (at 2, 3, ..., 9)
772                       call gxstx(alabl(1),alabl(3),slog(i))
773                       a1=a1+wsused
774                    endif
775                    if(impfl.eq.0) then
776                       impfl=1
777                       !--- plot power of ten between first and second minor label
778                       alabl(k1)=alabl(k1)                                 &
779                            +.5*(min(axup,alp+alogv(i+1))-alp)*fwc
780                       call gxppow(alabl,ia)
781                       a1=a1+spwlog
782                    endif
783                 endif
784              endif
785           enddo
786           ia=ia+1
787           goto 80
788100        continue
789        endif
790     endif
791  endif
792  !--- axis title
793  call gxpnbl(textin, ifirst, ilast)
794  if (iscloc .ne. 0 .and. labflg)  then
795     ispchl = max(1, index(textin(:ilast), stsep))
796     isradc = index(textin(ispchl:ilast), '<#>')
797     if (isradc .eq. 0)  then
798        sltext = '<#>[*10**($$$)]'
799     else
800        sltext = '   [*10**($$$)]'
801     endif
802     write(sltext(11:13), '(i3)') iscloc
803     if (ifirst .eq. 0)  then
804        text = sltext
805     else
806        text = textin(ifirst:ilast) // sltext
807     endif
808  else
809     text = textin
810  endif
811  call gxpnbl(text,ifirst,ilast)
812  if(ifirst.ne.0.and.itext.ne.0.and.cuhigh.gt.0.)  then
813     !--- set correct character height (viewports !), get width
814     call gxschf(1,iaxort,cthigh,chhigh,chwdth)
815     if(xaxis)  then
816        sgspac=-1.75 * chhigh
817     else
818        sgspac=1.5 * chhigh
819     endif
820     if(naxal.lt.1.or.naxal.gt.3)  naxal=2
821     if(naxal.eq.1)  then
822        atext(k1)=cnt(k1)
823     elseif(naxal.eq.2)  then
824        atext(k1)=.5*(cnt(k1)+cnt(k1+1))
825     else
826        atext(k1)=cnt(k1+1)
827     endif
828     if(itext.eq.2)  then
829        atext(k2)=max(tick(k2),tick(k2+1),alabl(k2),alabl(k2+1))      &
830             +space
831     else
832        atext(k2)=min(tick(k2),tick(k2+1),alabl(k2),alabl(k2+1))      &
833             - 2.5 * space
834     endif
835     !--- get number of separation characters
836     call gxchct(text(ifirst:ilast),stsep,nchct)
837     nlines=nchct+1
838     if(xaxis)  then
839        if(itext.eq.2)  atext(k2)=atext(k2)+1.5*nlines*chhigh
840     else
841        if(itext.eq.1)  atext(k2)=atext(k2)-1.5*nlines*chhigh
842     endif
843     !--- write line by line
844     irf=1
845110  continue
846     isp=index(text(irf:ilast),stsep)
847     if(isp.eq.0)  then
848        isp=ilast
849     else
850        isp=irf+isp-2
851     endif
852     if(isp.ge.irf)  then
853        stext=text(irf:isp)
854        l=isp+1-irf
855        call gxpnbl(stext(:l),ifs,ils)
856        in=index(stext(:l),'<#>')
857        if(in.eq.0)  then
858           call jstxal(naxal,1)
859           if(ifs.gt.0)  call gxtx(atext(1),atext(3),stext(:ils))
860        else
861           !--- split line into left and right adjusted part
862           l1=in-1
863           l2=in+3
864           if(l1.gt.0)  then
865              call jstxal(1,1)
866              sk=atext(k1)
867              atext(k1)=cnt(k1)
868              call gxtx(atext(1),atext(3),stext(:l1))
869              atext(k1)=sk
870           endif
871           if(l2.le.ils)  then
872              call jstxal(3,1)
873              sk=atext(k1)
874              atext(k1)=cnt(k1+1)
875              call gxtx(atext(1),atext(3),stext(l2:ils))
876              atext(k1)=sk
877           endif
878        endif
879     endif
880     irf=isp+2
881     if(irf.le.ilast)  then
882        atext(k2)=atext(k2)+sgspac
883        goto 110
884     endif
885  endif
886  !
887  !--- restore user settings
888  !
889  call gxrest(isave,rsave)
890999 end subroutine gxaxis
891subroutine gxchct(stext,sch,n)
892  implicit none
893  integer ilast,irf,isp,n
894  !***********************************************************************
895  !
896  !   Purpose: counts number of given characters in a string
897  !
898  !--- Input
899  !   stext      string
900  !   sch        special character
901  !--- Output
902  !   n          number of occurences
903  !
904  !   Author: H. Grote / CERN                        date: June 16, 1987
905  !                                           last mod: June 16, 1987
906  !
907  !***********************************************************************
908  character stext*(*),sch*1
909  n=0
910  irf=1
911  ilast=len(stext)
91210 continue
913  isp=index(stext(irf:),sch)
914  if(isp.gt.0) then
915     n=n+1
916     irf=irf+isp
917     if(irf.le.ilast) goto 10
918  endif
919end subroutine gxchct
920subroutine gxclos
921  use gxx11_common
922  implicit none
923  !***********************************************************************
924  !
925  !   Purpose: close terminal workstation
926  !
927  !   Author: H. Grote / CERN                        date: Feb. 26, 1988
928  !                                           last mod: Feb. 26, 1988
929  !
930  !***********************************************************************
931  call gxundf
932  if(lacttm.eq.lundef)  then
933     if(interm.gt.0)  then
934        call wdawk(interm)
935        call wclwk(interm)
936        lacttm=0
937     endif
938  endif
939end subroutine gxclos
940subroutine gxclrw
941  use gxx11_common
942  implicit none
943  !***********************************************************************
944  !
945  !   Purpose: clears open workstations, sets new picture name
946  !
947  !   Author: H. Grote / CERN                        date: June 16, 1987
948  !                                           last mod: March 2, 1988
949  !
950  !***********************************************************************
951
952  call gxundf
953  if(iclear .ne. 0) then
954     call gclrwk(0, 1)
955     iclear = 0
956     if (iepsop .eq. 2)  then
957        call gxopps(0, 0)
958        call wclwk(inmeta)
959        close(imetps)
960        iepsop = -iepsop
961     endif
962  endif
963end subroutine gxclrw
964subroutine gxcubi(npoint,xx,yy,yy1d,yy2d,ierror)
965  implicit none
966  integer i,ierror,n,npoint
967  real xx,yy,yy1d,yy2d
968  !***********************************************************************
969  !
970  !   new (internal) double precision version 29.1.88
971  !
972  !   calculates a third order natural spline through function values
973  !   yy(i), i=1,...,NPOINT, at knots XX(I) (XX(I+1) > XX(I))
974  !
975  !---  Input
976  !   npoint  number of knots and dimension of XX, YY, YY1D, YY2D
977  !          minimum value = 3
978  !   xx(i)   x values,  XX(I) < XX(I+1)  for all I
979  !   yy(i)   function values
980  !
981  !---  Output
982  !   yy1d(i) first derivative of third order pol. in interval I,
983  !          at point XX(I)
984  !   yy2d(i) second derivative
985  !   ierror  0 if everything OK, else number of the first x value found
986  !          that is smaller or equal to the previous one, or -1 if NPOINT < 3
987  !
988  !++++++ warning: all first and second derivatives set to zero if the
989  !    condition XX(I+1) > XX(I) is not fulfilled for I = [1,n-1] (IERROR > 0)
990  !
991  !--- remark: very near to routine SPLIN3 in CERN library, E209
992  !
993  !   Author hG                         13.11.86   last mod. 29.1.88
994  !
995  !***********************************************************************
996  dimension xx(*),yy(*),yy1d(*),yy2d(*)
997  double precision zero,half,one,three,third,dfac,dx1,dx2,dy1,dy2,  &
998       dd,dyx1,dyx2,divdif,alf,bet
999  save zero,half,one,three
1000  data zero,half,one,three/0.d0,0.5d0,1.d0,3.d0/
1001  third=one/three
1002  ierror=0
1003  n=npoint
1004  yy2d(1)=0.
1005  yy2d(n)=0.
1006  yy1d(1)=0.
1007  !
1008  !--- method: see long write-up of E209. Basically, the second
1009  !   derivatives are found first from the solution of N-2 equations.
1010  !   the first and last second order derivative are set to zero (hence
1011  !   natural spline). The equations form a three-diagonal matrix.
1012  !   in a first pass, all but the latest unknown are
1013  !   eliminated, in the second pass all are then calculated by going
1014  !   backwards.
1015  !--- yy1d serves temporarily as intermediate storage for the factors
1016  !   in the first pass of this process.
1017  !
1018  if(n.eq.3)  then
1019     !--- only three points - direct solution
1020     dx1=xx(2)-xx(1)
1021     if(dx1.le.zero)  then
1022        ierror=2
1023        goto 40
1024     endif
1025     dx2=xx(3)-xx(2)
1026     if(dx2.le.zero)  then
1027        ierror=3
1028        goto 40
1029     endif
1030     dy1=yy(2)-yy(1)
1031     dy2=yy(3)-yy(2)
1032     dd=one/(dx1+dx2)
1033     dyx1=dy1/dx1
1034     dyx2=dy2/dx2
1035     yy2d(2)=three*dd*(dyx2-dyx1)
1036     yy1d(1)=dyx1-dx1*yy2d(2)*half*third
1037     yy1d(3)=dyx2+dx2*yy2d(2)*half*third
1038     yy1d(2)=yy1d(1)+half*dx1*yy2d(2)
1039  elseif(npoint.gt.3)  then
1040     dx2=xx(2)-xx(1)
1041     if(dx2.le.zero)  then
1042        ierror=2
1043        goto 40
1044     endif
1045     dyx2=(yy(2)-yy(1))/dx2
1046     do i=2,n-1
1047        dx1=dx2
1048        dx2=xx(i+1)-xx(i)
1049        if(dx2.le.zero)  then
1050           ierror=i+1
1051           goto 40
1052        endif
1053        dyx1=dyx2
1054        dyx2=(yy(i+1)-yy(i))/dx2
1055        dd=one/(dx1+dx2)
1056        divdif=dd*(dyx2-dyx1)
1057        alf=half*dd*dx1
1058        bet=half-alf
1059        !
1060        !--- the following IF is only necessary for splines other than natural
1061        !
1062        if(i.eq.2)  then
1063           divdif=divdif-third*alf*yy2d(1)
1064        elseif(i.eq.n-1)  then
1065           divdif=divdif-third*bet*yy2d(n)
1066        endif
1067        dfac=one/(one+alf*yy1d(i-1))
1068        yy1d(i)=-dfac*bet
1069        yy2d(i)=dfac*(three*divdif-alf*yy2d(i-1))
1070     enddo
1071     !
1072     !--- now the last unknown derivative, YY2D(N-1), has been calculated.
1073     !   the others follow from going up the system.
1074     do i=n-2,1,-1
1075        dd=yy1d(i)
1076        yy2d(i)=dd*yy2d(i+1)+yy2d(i)
1077     enddo
1078     !
1079     !--- now the first derivatives from a direct equation (not the one
1080     !   given in the E-209 writeup - it can be simplified)
1081     !
1082     do i=1,n-1
1083        dx2=xx(i+1)-xx(i)
1084        dyx2=(yy(i+1)-yy(i))/dx2
1085        yy1d(i)=dyx2-dx2*third*(yy2d(i)+half*yy2d(i+1))
1086     enddo
1087     dx2=xx(n)-xx(n-1)
1088     dyx2=(yy(n)-yy(n-1))/dx2
1089     yy1d(n)=dyx2+dx2*third*(yy2d(n)+half*yy2d(n-1))
1090  else
1091     !
1092     !--- n < 3: error exit as well
1093     ierror=-1
1094     goto 40
1095  endif
1096  goto 999
109740 continue
1098  !
1099  !--- error condition: all first and second derivatives to zero
1100  !
1101  do i=1,n
1102     yy1d(i)=0.
1103     yy2d(i)=0.
1104  enddo
1105999 end subroutine gxcubi
1106function gxcubv(x,npoint,xx,yy,yy1d,yy2d)
1107  implicit none
1108  integer i,npoint
1109  real gxcubv,x,xx,yy,yy1d,yy2d
1110  !***********************************************************************
1111  !
1112  !   new (internal) double precision version
1113  !
1114  !   calculates the value of a third order spline at X. The routine
1115  !   gxcubi must be called beforehand.
1116  !
1117  !---  Input
1118  !   x       abscissa value. For X outside [XX(1),XX(npoint)], a linear
1119  !          extrapolation is performed.
1120  !   npoint  number of knots and dimension of XX, YY, YY1D, YY2D
1121  !          minimum value = 3
1122  !   xx(i)   x values,  XX(I) < XX(I+1)  for all I
1123  !   yy(i)   function values
1124  !   yy1d(i) first derivative of third order pol. in interval I,
1125  !          at point XX(I), from GXCUBI
1126  !   yy2d(i) second derivative, from GXCUBI
1127  !
1128  !   Author hG                         13.11.86   last mod. 29.1.88
1129  !
1130  !***********************************************************************
1131  dimension xx(*),yy(*),yy1d(*),yy2d(*)
1132  double precision half,dx,h2,h3,h4,h5,h6
1133  save half
1134  data half/0.5d0/
113510 continue
1136  if(x.le.xx(1))  then
1137     dx=x-xx(1)
1138     gxcubv=yy(1)+yy1d(1)*dx
1139  elseif(x.ge.xx(npoint))  then
1140     dx=x-xx(npoint)
1141     gxcubv=yy(npoint)+yy1d(npoint)*dx
1142  else
1143     do i=1,npoint-1
1144        if(x.lt.xx(i+1)) goto 30
1145     enddo
114630   continue
1147     dx=x-xx(i)
1148     h4=yy2d(i)
1149     h6=(yy2d(i+1)-h4)/(xx(i+1)-xx(i))
1150     h2=half*h4
1151     h5=half*h6
1152     h3=h5/3.d0
1153     gxcubv=((h3*dx+h2)*dx+yy1d(i))*dx+yy(i)
1154     !   first derivative in X  = (H5*DX+H4)*DX+YY1D(I)
1155     !   second    "      "  "  = H6*DX+H4
1156  endif
1157end function gxcubv
1158subroutine gxcrv1(nset,nptval,ipxval,ipyval,icvref,xval,yval,window,actwin,ierr)
1159  use gxx11_common
1160  implicit none
1161  integer ibar,ic,ierr,isplin,isym,j,kset,line,nset,mark
1162  real dum1,dum2,fsx,fsy,xs,ys
1163  !***********************************************************************
1164  !
1165  !   Purpose: plots curves into an existing frame, clips
1166  !
1167  !--- Input
1168  !   nset       number of curves (=ordered sets of (x,y) pairs) to plot
1169  !   nptval(i)  number of points ((x,y) pairs) in set I
1170  !   ipxval(i)  first x value of set I in array XVAL
1171  !   ipyval(i)  first y value of set I in array YVAL
1172  !   icvref(i)  number of the parameter set to be used for curve I. This value
1173  !            will be forced into [1,MAXSET].
1174  !            The x and y axis reference numbers of set I will be taken
1175  !            from this parameter set. All x and y axes with the
1176  !            corresponding reference numbers will be (scaled if automatic)
1177  !            and plotted together with set I.
1178  !            If no x resp. y axis exists with the reference number
1179  !            from the parameter set, the curve will be plotted with
1180  !            automatic scaling, but without x resp. y axis.
1181  !   xval       array containing the x values for all sets
1182  !   yval       array containing the y values for all sets
1183  !   window(j,I) GKS window (J=1...4) to be used with curve I. These values
1184  !            can be obtained from routines GXFRAM or GXFRM1
1185  !   actwin(j,I) active window (J=1...4) to clip curve I. These values
1186  !            can be obtained from routine GXFRM1
1187  !--- Output
1188  !   ierr       0 if everything OK, else GKS error, or
1189  !            1 : GXINIT not called (initialization)
1190  !
1191  !   Author: H. Grote / CERN                        date: Dec. 9, 1988
1192  !                                           last mod: Dec. 9, 1988
1193  !
1194  !***********************************************************************
1195
1196  integer nptval(*),ipxval(*),ipyval(*),icvref(*)
1197  real xval(*),yval(*),window(4,*),actwin(4,*)
1198  real wn(4),ac(4),xx(2),yy(2),rsave(20)
1199  integer isave(20)
1200  character sss*1
1201  !
1202  !--- get current user settings and keep them
1203  call gxsave(isave,rsave,ierr)
1204  if(ierr.ne.0)  goto 999
1205  !--- set reasonable defaults for plot style
1206  call gxspmt
1207  !--- loop over curves
1208  do ic=1,nset
1209     !--- get curve parameter set ref.
1210     kset=max(1,min(maxset,icvref(ic)))
1211     !--- get curve plot parameters
1212     line=icvpar(4,kset)
1213     ibar=icvpar(7,kset)
1214     isplin=icvpar(5,kset)
1215     mark=min(5,icvpar(8,kset))
1216     if(mark.ne.0) then
1217        isym=0
1218     else
1219        isym=icvpar(9,kset)
1220     endif
1221     !--- set window
1222     do j=1,4
1223        ac(j)=actwin(j,kset)
1224        wn(j)=window(j,kset)
1225     enddo
1226     call jswn(inormt,wn(1),wn(2),wn(3),wn(4))
1227     !     call jselnt(inormt)
1228     !
1229     !--- plot curves
1230     !
1231     !   color index and line thickness
1232     if(line.ne.0.or.ibar.ne.0) then
1233        call jsplci(icvpar(6,kset))
1234        call jslwsc(float(icvpar(3,kset)))
1235     endif
1236     if(line.ne.0) then
1237        !   polyline style
1238        call jsln(line)
1239        if(isplin.eq.0)  then
1240           !   plot polyline
1241           call gxpl(nptval(ic),xval(ipxval(ic)),yval(ipyval(ic)),ac)
1242        else
1243           !   smooth with a third order spline
1244           call gxplt1(nptval(ic),xval(ipxval(ic)),yval(ipyval(ic)),   &
1245                ac)
1246        endif
1247     endif
1248     if(mark.ne.0) then
1249        !   set marker type
1250        call jsmk(mark)
1251        !   plot marker at point positions
1252        call gxpm(nptval(ic),xval(ipxval(ic)),yval(ipyval(ic)),ac)
1253     endif
1254     if(ibar.ne.0) then
1255        !   vertical bars to lower x axis position (whether x axis plotted or not)
1256        yy(1)=axwndy(1,kset)
1257        call jsln(1)
1258        do j=0,nptval(ic)-1
1259           xx(1)=xval(ipxval(ic)+j)
1260           xx(2)=xx(1)
1261           yy(2)=yval(ipyval(ic)+j)
1262           call gxpl(2,xx,yy,ac)
1263        enddo
1264     endif
1265     if(isym.ne.0) then
1266        !--- center character on point
1267        call jstxal(2,3)
1268        !--- set character height
1269        call gxschf(1,1,0.001*icvpar(10,kset),dum1,dum2)
1270        !--- get plot character
1271        sss=splotc(kset:kset)
1272        !--- set ndc because of character sizes  (curves with different scales)
1273        call jswn(inormt,0.,1.,0.,1.)
1274        !        call jselnt(inormt)
1275        fsx=1./(wn(2)-wn(1))
1276        fsy=1./(wn(4)-wn(3))
1277        do j=0,nptval(ic)-1
1278           xs=fsx*(xval(ipxval(ic)+j)-wn(1))
1279           ys=fsy*(yval(ipyval(ic)+j)-wn(3))
1280           call gxtx1(xs,ys,sss,ac)
1281        enddo
1282     endif
1283  enddo
1284  !--- restore previous settings
1285  call gxrest(isave,rsave)
1286999 end subroutine gxcrv1
1287subroutine gxcurv(nset,nptval,ipxval,ipyval,icvref,xval,yval,window,ierr)
1288  use gxx11_common
1289  implicit none
1290  integer ibar,ic,ierr,isplin,isym,j,kset,line,nset,mark
1291  real dum1,dum2,fsx,fsy,xs,ys
1292  !***********************************************************************
1293  !
1294  !   Purpose: plots curves into an existing frame
1295  !
1296  !--- Input
1297  !   nset       number of curves (=ordered sets of (x,y) pairs) to plot
1298  !   nptval(i)  number of points ((x,y) pairs) in set I
1299  !   ipxval(i)  first x value of set I in array XVAL
1300  !   ipyval(i)  first y value of set I in array YVAL
1301  !   icvref(i)  number of the parameter set to be used for curve I. This value
1302  !            will be forced into [1,MAXSET].
1303  !            The x and y axis reference numbers of set I will be taken
1304  !            from this parameter set. All x and y axes with the
1305  !            corresponding reference numbers will be (scaled if automatic)
1306  !            and plotted together with set I.
1307  !            If no x resp. y axis exists with the reference number
1308  !            from the parameter set, the curve will be plotted with
1309  !            automatic scaling, but without x resp. y axis.
1310  !   xval       array containing the x values for all sets
1311  !   yval       array containing the y values for all sets
1312  !   window(j,I) GKS window (J=1...4) to be used with curve I. These values
1313  !            can be obtained from routine GXFRAM
1314  !--- Output
1315  !   ierr       0 if everything OK, else GKS error, or
1316  !            1 : GXINIT not called (initialization)
1317  !
1318  !   Author: H. Grote / CERN                        date: June 16, 1987
1319  !                                           last mod: March 7, 1988
1320  !
1321  !***********************************************************************
1322
1323  integer nptval(*),ipxval(*),ipyval(*),icvref(*)
1324  real xval(*),yval(*),window(4,*)
1325  real wn(4),xx(2),yy(2),rsave(20)
1326  integer isave(20)
1327  character sss*1
1328  !
1329  !--- get current user settings and keep them
1330  call gxsave(isave,rsave,ierr)
1331  if(ierr.ne.0)  goto 999
1332  !--- set reasonable defaults for plot style
1333  call gxspmt
1334  !--- loop over curves
1335  do ic=1,nset
1336     !--- get curve parameter set ref.
1337     kset=max(1,min(maxset,icvref(ic)))
1338     !--- get curve plot parameters
1339     line=icvpar(4,kset)
1340     ibar=icvpar(7,kset)
1341     isplin=icvpar(5,kset)
1342     mark=min(5,icvpar(8,kset))
1343     if(mark.ne.0) then
1344        isym=0
1345     else
1346        isym=icvpar(9,kset)
1347     endif
1348     !--- set window
1349     do j=1,4
1350        wn(j)=window(j,kset)
1351     enddo
1352     call jswn(inormt,wn(1),wn(2),wn(3),wn(4))
1353     !     call jselnt(inormt)
1354     !
1355     !--- plot curves
1356     !
1357     !   color index and line width
1358     if(line.ne.0.or.ibar.ne.0) then
1359        call jsplci(icvpar(6,kset))
1360        call jslwsc(float(icvpar(3,kset)))
1361     endif
1362     if(line.ne.0) then
1363        !   polyline style
1364        call jsln(line)
1365        if(isplin.eq.0)  then
1366           !   plot polyline
1367           call gvpl(nptval(ic),xval(ipxval(ic)),yval(ipyval(ic)))
1368        else
1369           !   smooth with a third order spline
1370           call gxplts(nptval(ic),xval(ipxval(ic)),yval(ipyval(ic)))
1371        endif
1372     endif
1373     if(mark.ne.0) then
1374        !   set marker type
1375        call jsmk(mark)
1376        !   plot marker at point positions
1377        call gvpm(nptval(ic),xval(ipxval(ic)),yval(ipyval(ic)))
1378     endif
1379     if(ibar.ne.0) then
1380        !   vertical bars to lower x axis position (whether x axis plotted or not)
1381        yy(1)=axwndy(1,kset)
1382        call jsln(1)
1383        do j=0,nptval(ic)-1
1384           xx(1)=xval(ipxval(ic)+j)
1385           xx(2)=xx(1)
1386           yy(2)=yval(ipyval(ic)+j)
1387           call gvpl(2,xx,yy)
1388        enddo
1389     endif
1390     if(isym.ne.0) then
1391        !--- center character on point
1392        call jstxal(2,3)
1393        !--- set character height
1394        call gxschf(1,1,0.001*icvpar(10,kset),dum1,dum2)
1395        !--- get plot character
1396        sss=splotc(kset:kset)
1397        !--- set ndc because of character sizes  (curves with different scales)
1398        call jswn(inormt,0.,1.,0.,1.)
1399        !        call jselnt(inormt)
1400        fsx=1./(wn(2)-wn(1))
1401        fsy=1./(wn(4)-wn(3))
1402        do j=0,nptval(ic)-1
1403           xs=fsx*(xval(ipxval(ic)+j)-wn(1))
1404           ys=fsy*(yval(ipyval(ic)+j)-wn(3))
1405           call gxstx(xs,ys,sss)
1406        enddo
1407     endif
1408  enddo
1409  !--- restore previous settings
1410  call gxrest(isave,rsave)
1411999 end subroutine gxcurv
1412subroutine gxdfmt(axlow,axup,intv,ival,iscal,fmt)
1413  implicit none
1414  integer i,i1,i2,ii,intv,iscal,ival,j,mform
1415  real axl,axlow,axu,axup,fact,step,up,x,y
1416  !***********************************************************************
1417  !
1418  !   Purpose: calculates reasonable format for axis labels
1419  !
1420  !--- Input
1421  !   axlow, aXUP  axis range
1422  !   intv         no. of intervals, or 0 if not known
1423  !--- Output
1424  !   ival         length of format (e.g. 8 for F8.2)
1425  !   iscal        power of 10 extracted from axlow and axup
1426  !   fmt          format in correct form, e.g. '(F8.2)'
1427  !
1428  !   Author: H. Grote / CERN                        date: June 16, 1987
1429  !                                           last mod: Feb. 25, 1991
1430  !
1431  !***********************************************************************
1432  character fmt *(*)
1433  parameter (mform=8)
1434  character form(mform)*8
1435  integer iv(mform),ic(mform)
1436  save form, iv, ic, up
1437  data form/'(G10.4)','(F6.1)','(F6.2)','(F5.2)','(F6.3)', '(F7.4)',&
1438       '(F8.5)','(F9.6)'/
1439  data iv/10,6,6,5,6,7,8,9/
1440  data ic/4,1,2,2,3,4,5,6/
1441  data up/999./
1442  x=max(abs(axlow),abs(axup))
1443  if (x .eq. 0.)  then
1444     iscal = 0
1445     i = 1
1446     goto 30
1447  endif
1448  i1 = log10(x)
1449  if (i1 .gt. 3 .or. i1 .le. -3)  then
1450     iscal = 3 * (i1 / 3)
1451  else
1452     iscal = 0
1453  endif
1454  fact = 10.**(-iscal)
1455  axl = fact * axlow
1456  axu = fact * axup
1457  y=axu-axl
1458  if (intv .gt. 0)  then
1459     !--- get all digits of step if possible
1460     step = y / intv
1461     do  i1 = 0, 4
1462        if (step .ge. 0.99                                            &
1463             .and. step - int(step + 0.5) .lt. 0.01)  goto 2
1464        step = 10. * step
1465     enddo
14662    step = y / intv + abs(axl) - int(abs(axl))
1467     do  i2 = 0, 4
1468        if (step - int(step + 0.0001) .lt. 0.01)  goto 4
1469        step = 10. * step
1470     enddo
14714    i = max(i1, i2)
1472     ii = abs(log10(x)) + 1.001
1473     if (axl .lt. 0.)                                                &
1474          ii = max( max(log10(x), log10(-axl) + 1.) + 1.001, 2.001)
1475     if (i + ii .ge. 9)  then
1476        i = 1
1477        goto 30
1478     else
1479        ival = i + ii + 1
1480        fmt = ' '
1481        write(fmt(:6), '(''(F'',I1,''.'',I1,'')'')')  ival, i
1482     endif
1483     goto 999
1484  else
1485     do i=1,mform
1486        if(x.ge.up) goto 20
1487        x=10.*x
1488     enddo
1489     i=1
1490     goto 30
149120   continue
1492     ii=i
1493     do  j=ii,mform
1494        if(y.ge.10.**(1-ic(i)))  goto 30
1495        i=i+1
1496     enddo
1497     i=1
1498  endif
149930 continue
1500  fmt=form(i)
1501  ival=iv(i)
1502999 end subroutine gxdfmt
1503subroutine gxdfvm(sin,sout,nml)
1504  implicit none
1505  integer i1,i2,i3,i4,jb1,jb2,nml
1506  !***********************************************************************
1507  !
1508  !   Purpose: returns the VM filename (fn ft fm)
1509  !
1510  !--- Input
1511  !   sin        ruser Input - either fn, or fn ft, or fn ft fm
1512  !--- Output
1513  !   sout       complete fn ft fm filename
1514  !   nml        last character of file name in SIN
1515  !
1516  !   Author: H. Grote / CERN                        date: April 7, 1988
1517  !                                           last mod: April 7, 1988
1518  !
1519  !***********************************************************************
1520  character(*)  sin,sout
1521  character(20) sloc
1522  call gxpnbl(sin,i1,i2)
1523  if(i1.eq.0)  then
1524     !--- user Input is totally blank
1525     sloc='GXMETA   METAFILE A'
1526     nml=1
1527     goto 500
1528  endif
1529  jb1=index(sin(i1:i2),' ')
1530  if(jb1.eq.0)  then
1531     !--- user Input is one piece
1532     sloc=sin(i1:i2)
1533     sloc(9:)=' METAFILE A'
1534     nml=i2
1535     goto 500
1536  endif
1537  jb1=jb1+i1-1
1538  call gxpnbl(sin(jb1:),i3,i4)
1539  i3=i3+jb1-1
1540  jb2=index(sin(i3:i2),' ')
1541  nml=jb1-1
1542  if(jb2.eq.0)  then
1543     !--- user Input two pieces
1544     sloc=sin(i1:i2)//' A'
1545  else
1546     !--- user Input three pieces
1547     sloc=sin(i1:i2)
1548  endif
1549500 sout=sloc
1550end subroutine gxdfvm
1551subroutine gxdint(axlow,axup,intv)
1552  implicit none
1553  integer i,intv,mrange
1554  real axlow,axup,d,dn,x
1555  !***********************************************************************
1556  !
1557  !   Purpose: calculates reasonable number of axis intervals
1558  !
1559  !--- Input
1560  !   axlow, aXUP  axis range
1561  !--- Output
1562  !   intv         number of intervals
1563  !
1564  !   Author: H. Grote / CERN                        date: June 16, 1987
1565  !                                           last mod: June 16, 1987
1566  !
1567  !***********************************************************************
1568  parameter (mrange=10)
1569  integer iv(mrange)
1570  real rangl(mrange)
1571  save iv, rangl
1572  data iv/10,6,8,10,10,6,8,10,6,8/
1573  data rangl/1.,1.2,1.6,2.,2.5,3.,4.,5.,6.,8./
1574  d=axup-axlow
1575  if(d.gt.0.)  then
1576     x=100.+log10(d)
1577     dn=10.**(x-int(x + 0.0001))
1578     do i=1,mrange
1579        if(abs(dn-rangl(i))/rangl(i).lt.1.e-3)  then
1580           intv=iv(i)
1581           goto 999
1582        endif
1583     enddo
1584  endif
1585  intv=10
1586999 end subroutine gxdint
1587subroutine gxeopn(string,number)
1588  use gxx11_common
1589  implicit none
1590  integer number
1591  !***********************************************************************
1592  !
1593  !   Purpose: transfers unit number to common block for files opened
1594  !         externally
1595  !
1596  !--- Input
1597  !   string  (character) option :
1598  !         'mETA' for metafile, 'ERROR' for error file
1599  !   number  unit number
1600  !
1601  !   Author: H. Grote / CERN                        date: Dec. 21, 1987
1602  !
1603  !***********************************************************************
1604
1605  character string *(*),sloc *4
1606  call gxundf
1607  sloc=string
1608  if(sloc.eq.'META')  then
1609     lmetop=lundef
1610     call gxsvar('IMETUN',number,0.,' ')
1611  elseif(sloc.eq.'ERRO')  then
1612     lerrop=lundef
1613     call gxsvar('IERRUN',number,0.,' ')
1614  endif
1615end subroutine gxeopn
1616subroutine gxfchr(imode, ch, ifont, width, np, ipen, x, y, ierr)
1617  implicit none
1618  integer i,ierr,ifont,imode,ip,ipos,isel,istr,iwid,j,k,kbit,kword, &
1619       lx,ly,np
1620  real width
1621  !***********************************************************************
1622  !
1623  !   Purpose: returns the polygon for a character
1624  !
1625  !--- Input:
1626  !   imode    =0: give character widths only, else give all
1627  !   ch       character
1628  !   ifont    font (only 1 or -13)
1629  !--- Output:
1630  !   width    character width
1631  !   np       # points in polygon
1632  !   ipen     0 for pen up, 1 for pen down
1633  !   x        x coordinates
1634  !   y        y coordinates
1635  !   ierr     =0: OK, =1: wrong font, =2: character not found
1636  !
1637  !***********************************************************************
1638  character(1) ch
1639  real x(*), y(*)
1640  integer ipen(*)
1641  integer nchinf(2), ichinf(95,2), ichcod(652,2)
1642  character(100) chstr(2)
1643  save chstr, nchinf, ichinf, ichcod
1644  data nchinf / 95, 91 /
1645  data chstr /                                                      &
1646       ' !"#$%&''()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[/]^_`abcdefghijklmnopqrstuvwxyz{|}~',&
1647       ' !"#$%&''()*+,-./0123456789:;<=>?@ABCDEFGHIKLMNOPRSTUVWXYZ[/]^_`abcdefghiklmnoprstuvwxyz{|}~' /
1648  data (ichinf(j,1), j = 1,  95) /  541065217, 556276737, 574633992,&
1649       592715798, 609247262, 627078198, 644384851, 656940149, 674769020, &
1650       691546246, 708843664, 728240278, 740827290, 761792674, 774378660, &
1651       794298537, 810566827, 827330748, 844118208, 860896462, 877663453, &
1652       894452962, 911236339, 927994122, 944796942, 961568043, 975710530, &
1653       992490828,1012927833,1030230364,1046482272,1061703011,1080862070, &
1654       1095244191,1112823205,1129597370,1146370508,1162617306,1179130338,&
1655       1196709352,1213733373,1226836483,1245719045,1263802895,1279529493,&
1656       1298145817,1314396705,1331189287,1347695164,1364745800,1381251679,&
1657       1397772909,1413485185,1431841413,1447563919,1465918099,1481642651,&
1658       1497896607,1515199140,1530403498,1549273776,1563957938,1582829240,&
1659       1600654011,1613242045,1632387780,1649165012,1665678052,1682719474,&
1660       1699235586,1714429715,1733056282,1749821231,1763712824,1781017407,&
1661       1799625545,1814039375,1836598097,1850484577,1867269994,1884046203,&
1662       1900823435,1916018587,1933854626,1949310899,1967925178,1983910851,&
1663       2002265031,2017727439,2034246611,2051283931,2067290081,2082474998,&
1664       2100844536,2120232973/
1665  data (ichinf(j,2), j = 1,  95) /  541065217, 556276737, 574633992,&
1666       592715798, 609247262, 627078198, 644122707, 656940149, 674769020, &
1667       691546246, 708843664, 727978134, 740827290, 761530530, 774378660, &
1668       794298537, 810566827, 827330748, 844118208, 860896462, 877663453, &
1669       894452962, 911236339, 927994122, 944796942, 961568043, 975710530, &
1670       992490828,1012927833,1029968220,1046482272,1061703011,1080862070, &
1671       1095244191,1112823205,1129320890,1145575870,1162617284,1179667916,&
1672       1195643359,1213733347,1226836457,1263802859,1279791601,1298145781,&
1673       1314396669,1330659843,1347951123,1381249561,1397235237,1413485100,&
1674       1431852592,1447577157,1465401942,1481120358,1498963564,1515199107,&
1675       1530403465,1549273743,1563957905,1582829207,1600391834,1613242012,&
1676       1632918179,1649177273,1665675989,1682464481,1698711288,1717064457,&
1677       1733050141,1750091564,1764500285,1799897925,1816141653,1834240860,&
1678       1850225518,1868322682,1884826511,1917340569,1934641067,1951407036,&
1679       1967409090,1984970707,2002537442,2017487860,2035574798,2050774056,&
1680       2067289149,2082474066,2100843604,2120233065, 4 * 0/
1681  data (ichcod(j,1), j = 1, 117) /   43336327,  42091009,1115702017,&
1682       1115816725,1117012498,1108361871,1125139089, 102057364,1158825232,&
1683       1167017488,1167132057,1111951513,1162281484,1225523590,1216742425,&
1684       1145308697,1178863762,1200899605,1142243988,1100104080,1108230797,&
1685       1133266570,1200179208,1216759939,1199654400,1140867713,1099106965,&
1686       1098908693,1158890769,1150239630,1116619152,1100104212,1125467157,&
1687       1158956691,1209223572,1251281031,1199982340,1191331840,1224755713,&
1688       1250118277,1233602695, 193743757,1259227790,1242384779,1216759683,&
1689       1182877056,1132479105,1107444100,1099317768,1116292621,1183729424,&
1690       1192380052,1167410324,1142047760,1150109066,1208174849,1241533184,&
1691       1266764674,  51724948,1108492816,1116685072,1116800409,1150763924,&
1692       1116750347,1107772034,1136805061,1170669977,1117209492,1150305547,&
1693       1158104194,1136804549,1103561749,1141440914,1183581842,1099695762,&
1694       1182794249,1258881793,1115701761,1115833089,1128350403,1111753225,&
1695       1258881666,1107378816,1124156034, 169427271,  76890900,1108427148,&
1696       1099514372,1124156544,1166034689,1208240265,1217153041,1192510869,&
1697       1150616337,1142048149,1166017040,1108427411,1125401621,1175799572,&
1698       1200834577,1208960909,1183465856,1216348821,1209353485,1183664012,&
1699       1208699016,1216759811,1191265664,1140867713,1107444100, 110444935,&
1700       1225197205,1182795669,1117078028,1116554254,1166952205,1208699016/
1701  data (ichcod(j,1),j= 118, 234) / 1216759811,1191265664,1140867713,&
1702       1107444100, 135415700,1175799061,1133789841,1108099591,1115898753,&
1703       1157645696,1191266307,1216759943,1208633100,1166886157,1133265546,&
1704       1107757205,1132462485,1217725461,1117012498,1108361870,1133331852,&
1705       1191921673,1216825476,1208108929,1174422528,1115767298,1099186567,&
1706       1107903243,1150043789,1200506896,1209157524,1175798805, 135153547,&
1707       1183401224,1149780745,1108033934,1099907602,1125401749,1159022228,&
1708       1200769038,1208567684,1182876928,1140867713,1107493518,1108165260,&
1709       1124942478,  42091009,1115702017,1115816590,1108165260,1124942478,&
1710       50414208,1107378818,1124156225,1120092740, 168968713,1241514508,  &
1711       1259078150,1258684946,1242120704,  26231185,1108558484,1133856149,&
1712       1184122643,1200703375,1192052364,1149912199,  75645953,1149256961,&
1713       1149372685,1217349520,1175471375,1150174219,1141392518,1166362373,&
1714       1216760072, 152062214,1233472133,1267158026,1275874191,1259424275,&
1715       1226065813,1175798932,1133724305,1108296076,1099514374,1115964290,&
1716       1149322752,1199589633,1241664131,  76890240,  76892288,  34031367,&
1717       34947584,  34948757,1209288851,1225869583,1217218572,1183515147,  &
1718       1183533066,1216956679,1225017474,1208043136,1107298576,1217546132,&
1719       1184187541,1133789842,1108361613,1099448837,1115898753,1149257344,&
1720       1199655043,1225064981,1107296789,1167410964,1209157776,1225607432/
1721  data (ichcod(j,1),j= 235, 351) / 1216694275,1191265664,1107296789,&
1722       1107296789,1217724939,1175126528,1216348693,1107296789,1217724939,&
1723       1175128336,1217546132,1184187541,1133789842,1108361613,1099448837,&
1724       1115898753,1149257344,1199655043,1225083144, 109594888,  34947584,&
1725       152389888,  34294027,  34947584, 102057477,1166165249,1140867840, &
1726       1107378562,1090863367,  34947584, 152388103,  76302592,  34947584,&
1727       33572864,  34947584,  34948608, 169166336, 169167360,  34947584,  &
1728       34949376, 152389888,  76891028,1116881424,1099776392,1107640963,  &
1729       1132545152,1182812033,1216563461,1233668493,1225803922,1200899733,&
1730       1150616085,1107296789,1184188436,1217612049,1225672844,1208698506,&
1731       1107952789,1133789842,1108361613,1099448837,1115898753,1149257344,&
1732       1199655043,1225083272,1233996048,1217546132,1184187541, 100944194,&
1733       34947584,  34948757,1209288851,1225869583,1217218572,1183531531,  &
1734       93014272, 143804308,1175798805,1117012370,1099973134,1116554124,  &
1735       1183467401,1208502406,1216563073,1174422528,1115767171,  68502528,&
1736       9783189,  34947590,1115898753,1157645824,1199655043,1225148693,   &
1737       9782400, 144000128,  18170752, 102056832, 102058112, 185944192,   &
1738       26560640, 143999360,   9782411,1149241493,1149962389,1098908053,  &
1739       1217724800,1216348697,1111949849,1167655495,1170669849,1246168345,&
1740       1162281369,1159266759,1162281351,1166821767,  37964611,  34554512/
1741  data (ichcod(j,1),j= 352, 468) / 1125270292,1117078036,1116931982,&
1742       1199572875,1183663502,1141785357,1108033928,1099317763,1124156416,&
1743       1166034561,1199768085,1107296779,1124942862,1166952077,1200310280,&
1744       1208371075,1182877056,1140867841,1107494795,1183663502,1141785357,&
1745       1108033928,1099317763,1124156416,1166034561,1199769493,1199572875,&
1746       1183663502,1141785357,1108033928,1099317763,1124156416,1166034561,&
1747       1199767944,1200113546,1191986829,1166951438,1124942347,1099448710,&
1748       1107510017,1140868480,1182877571,  85279765,1125401233,1115685134,&
1749       1150158734,1203914565,1187399111,1145520966, 126568077,1166951438,&
1750       1124942347,1099448710,1107510017,1140868480,1182877571,  34947584,&
1751       34227085,1150174734,1192052618,1199571349,1108624021,1108754837,  &
1752       34488832,  43336468,1133855510,1117061902,1128481478,1103577287,  &
1753       34947584, 118374916,  67651456,  34947584,  34488832,  34227085,  &
1754       1150174734,1192052618,1199572874,1225607694,1267616909,1292520704,&
1755       34488832,  34227085,1150174734,1192052618,1199571982,1124942347,  &
1756       1099448710,1107510017,1140868480,1182877571,1208371208,1200309901,&
1757       1166951438,  34488903,  34292493,1141785998,1183664011,1208502278,&
1758       1199785601,1166033920,1124155907, 126764999, 126568077,1166951438,&
1759       1124942347,1099448710,1107510017,1140868480,1182877571,  34488832,&
1760       34095755,1133331598,1175324427,1183663374,1133396493,1099645449/
1761  data (ichcod(j,1),j= 469, 585) / 1124615559,1183205124,1191396993,&
1762       1157645184,1107378563,  43336324,1124156416,1157628174,1150157326,&
1763       1107575425,1132479744,1174488964, 126764928,  17712128, 118375424,&
1764       26100608,  93209472,  93210496, 160319360,  26101504, 118374784,  &
1765       17712128, 118375424,1128546886,1095188679, 118374784,  26101518,  &
1766       25184000,  77153176,1125597845,1116947217,1133528078,1141654282,  &
1767       1107903240,1141261316,1132610305,1119961795,1128612806,1153892889,&
1768       1111949977,1134052375,1150633107,1141982096,1125008140,1141523721,&
1769       1141392134,1124352898,1140933825,1153647685,1137066695,  25575816,&
1770       1108034316,1141654795,1191659526,1225148935,1250577036,  76891028,&
1771       1116881424,1099776392,1107640963,1132545152,1182812033,1216563461,&
1772       1233668493,1225803922,1200899733,1150615746,1251410569,1191772427,&
1773       1267400966,1267073296,1267728644,1266942219,1267400978,1267859723,&
1774       1108165390,1166952077,1200310144, 126437128,1174881160,1116225926,&
1775       1090797827,1098990208,1174423297,1199702549,1107378816,1132463633,&
1776       1175602580,1150632853,1117012498,1108361870,1133266187,1175012999,&
1777       1183139331,1157694221,1108033929,1099383301,1124287618,1166034498,&
1778       1178879430,1153909703,1120289348,1111688341,1082131605,1216348679,&
1779       1191641368,1100431896,1100562712, 119031703,1209550745,1192756373,&
1780       1133789842,1108361613,1099448837,1115898753,1149257344,1199655043/
1781  data (ichcod(j,1),j= 586, 652) / 1225083272,1233996048,1217546132,&
1782       1184187541,  35144343,1125663385,1108871192,1217874200,1218005016,&
1783       34947590,1115898753,1157645824,1199655043,1225148693,  43533079,  &
1784       1134052121,1117259672,1209485464,1209616280, 126764928, 126568077,&
1785       1166951438,1124942347,1099448710,1107510017,1140868480,1182877571,&
1786       34947732,1125466774,1108674069,1184122645,1184253461,  68043533,  &
1787       1108033928,1099317763,1124156416,1166034561,1199785990,1208502155,&
1788       1183663502,1141768725,1117012757,1117143573, 110446356,1200965398,&
1789       1184170510,1107575425,1132479744,1174488964, 126764928,  43336468,&
1790       1133855510,1117062677,1184122645,1184253461,  60113556,1108427264,&
1791       60114069,1167345170,1175471502,1150092173,1166886540,1200244743,  &
1792       1208371075,1182877056,1149256449,1115881472/
1793  data (ichcod(j,2),j=   1, 117) /   43336327,  42091009,1115702017,&
1794       1115816725,1117012498,1108361871,1125139089, 102057364,1158825232,&
1795       1167017488,1167132057,1111951513,1162281484,1225523590,1216742425,&
1796       1145308697,1178863762,1200899605,1142243988,1100104080,1108230797,&
1797       1133266570,1200179208,1216759939,1199654400,1140867713,1099106965,&
1798       1098908693,1158890769,1150239630,1116619152,1100104212,1125467157,&
1799       1158956691,1209223572,1251281031,1199982340,1191331840,1224755713,&
1800       1250118277,1233602695, 193743757,1259227790,1242384779,1216759683,&
1801       1182877056,1132479105,1107444100,1099317768,1116292621,1183729424,&
1802       1192380052,1167410324,1142047760,1150109066,1208174849,1241533184,&
1803       1266764674,  51724948,1108492816,1116685072,1116800409,1150763924,&
1804       1116750347,1107772034,1136805061,1170669977,1117209492,1150305547,&
1805       1158104194,1136804549,1103561749,1141440914,1183581842,1099695762,&
1806       1182794249,1258881793,1115701761,1115833089,1128350403,1111753225,&
1807       1258881666,1107378816,1124156034, 169427271,  76890900,1108427148,&
1808       1099514372,1124156544,1166034689,1208240265,1217153041,1192510869,&
1809       1150616337,1142048149,1166017040,1108427411,1125401621,1175799572,&
1810       1200834577,1208960909,1183465856,1216348821,1209353485,1183664012,&
1811       1208699016,1216759811,1191265664,1140867713,1107444100, 110444935,&
1812       1225197205,1182795669,1117078028,1116554254,1166952205,1208699016/
1813  data (ichcod(j,2),j= 118, 234) / 1216759811,1191265664,1140867713,&
1814       1107444100, 135415700,1175799061,1133789841,1108099591,1115898753,&
1815       1157645696,1191266307,1216759943,1208633100,1166886157,1133265546,&
1816       1107757205,1132462485,1217725461,1117012498,1108361870,1133331852,&
1817       1191921673,1216825476,1208108929,1174422528,1115767298,1099186567,&
1818       1107903243,1150043789,1200506896,1209157524,1175798805, 135153547,&
1819       1183401224,1149780745,1108033934,1099907602,1125401749,1159022228,&
1820       1200769038,1208567684,1182876928,1140867713,1107493518,1108165260,&
1821       1124942478,  42091009,1115702017,1115816590,1108165260,1124942478,&
1822       50414208,1107378818,1124156225,1120092740, 168968713,1241514508,  &
1823       1259078150,1258684946,1242120704,  26231185,1108558484,1133856149,&
1824       1184122643,1200703375,1192052364,1149912199,  75645953,1149256961,&
1825       1149372685,1217349520,1175471375,1150174219,1141392518,1166362373,&
1826       1216760072, 152062214,1233472133,1267158026,1275874191,1259424275,&
1827       1226065813,1175798932,1133724305,1108296076,1099514374,1115964290,&
1828       1149322752,1199589633,1241664131,  76890240,  76892288,  34031367,&
1829       34947584,  34948757,1209288851,1225869583,1217218572,1183515147,  &
1830       1183533066,1216956679,1225017474,1208043136,1107296661,1216348544,&
1831       1217725589,1082131605,1216348288,1216348693,1107296789,1217724939,&
1832       1175126528,1216349461,1157628944,1116684814,1099710857,1107772038/
1833  data (ichcod(j,2),j= 235, 351) / 1141196293,1199982599,1216956556,&
1834       1208895375,1175471120,  34947584,  34949141,  34947584, 152389888,&
1835       34294027,  34947584,  34947584, 152388103,  76302592,  76890240,  &
1836       76892288,  34947584,  34948608, 169166336, 169167360,  34947584,  &
1837       34949376, 152389888,  25183104,1107771787,1099907602,1125401749,  &
1838       1167410964,1209157775,1217087495,1182812288,  34947584, 152389888,&
1839       34949397,  34947584,  34948757,1209288851,1225869582,1217153035,  &
1840       1183465994,  18171019,1090519317,1209336064,1207960597,1140850837,&
1841       1200948373,1133789842,1108361613,1099448837,1115898753,1149257344,&
1842       1199655043,1225083272,1233996048,1217546132,1184187541,  17842450,&
1843       1100235285,1125467028,1142047886,1149241360,1209157524,1192576533,&
1844       1167344914,1150158229,1166016783,1099907598,1116357384,1132938502,&
1845       1174816647,1208502410,1225673103,1242497301,1209336587,1175126272,&
1846       1207960725,1133789842,1108361613,1099448837,1115898753,1149257344,&
1847       1199655043,1225083272,1233996048,1217546132,1184187541,  67847947,&
1848       143999360,  26560661,  25184384,  35209799,  35210649,  38225351, &
1849       18434631,  85542215,  26821913,  29836615,  25642380,1233584707,  &
1850       1262682639,1116750610,1125401237,1108624019,  76432269,1116422665,&
1851       1099317635,1107378944,1140868353,1183074183,1217087758,  76432782,&
1852       1175275147,1199785985,1216366848, 102057236,1142047502,1116422663/
1853  data (ichcod(j,2),j= 352, 468) / 1098989895, 102057749,1209223184,&
1854       1200506637,1175209100,  76301707,1183401735,1191462530,1174488320,&
1855       1140867841,1115832837,  17711630,1124877893,1195853895, 143542284,&
1856       1191789122,1095057607,  93209614,1124942347,1099448709,1107444353,&
1857       1132479616,1166100099,1191593737,1183597966,1150305298,1142178965,&
1858       1167410836,1200752268,1175274766,1133396621,1116422921,1149764744,&
1859       1116160389,1099121153,1124091008,1166100099,  67977996,1107968391,&
1860       1099186690,1115767680,1157645953,1208174854,1233734028,1217283982,&
1861       1183597960,1149453127,   9126285,1116619534,1141720204,1158235397,&
1862       1149241486,1208698761,1149256644,1128726666,1091322382,1125008269,&
1863       1133200135,1107297031,1141589261,1175340814,1208764425,1199851079,&
1864       51266055,1099121025,1107313408,1140999300,  51265792, 135088014,  &
1865       1192117773,1141457672,1116209800,1132938246,1157711232,1174423169,&
1866       9781653,1117012755,1191183374,1090519950,1086784266,1116029570,   &
1867       1132479616,1166100099,1200031886,1200047875,1191266176,1216366978,&
1868       1241776526,1125008008,1107509632, 135153547,1191790086,1149453057,&
1869       1098908686,1124942346,1099383172,1107378816,1132479617,1166280200,&
1870       1166296577,1182812032,1216432516,1241991690,1233996046,  76432000,&
1871       118376328,1208174720,  17515021,1133398542,  34095621,1115833089, &
1872       1140868352,1174488835,1199982473,1191986829,1166951566,1133331083/
1873  data (ichcod(j,2),j= 469, 570) / 1107836999, 151929870,1124942347,&
1874       1099448709,1107444353,1132479616,1166100099,1191593737,1183598093,&
1875       1158546830,1140850955,1108165518,1225655310,1124942347,1099448709,&
1876       1107444353,1132479616,1166100099,1191593737,1183598093,1158562830,&
1877       9060620,1108230926,1133331339,1116029570,1132479616,1174488835,   &
1878       1208436875,1217267733,1145503882,1091322382,1125008269,1133200134,&
1879       1124287361,1149257088,1191266307,1225148939,1250821397,1142178707,&
1880       1133659153,1167083280,  93340687,1125008012,1116357512,1158104583,&
1881       84361990,1107640707,1098990273,1153647940,1162232903,1128726666,  &
1882       1091322382,1125008269,1133200134,1124287361,1140868352,1174488836,&
1883       1199982601,1217284241,1209288469,1175799187,1167148558,1191921673,&
1884       1233585429,1142178707,1133659153,1167083280, 118506766,1133265417,&
1885       1099317636,1107444480,1153582404,1162233031,1137132357,  77153176,&
1886       1125597845,1116947217,1133528078,1141654282,1107903240,1141261316,&
1887       1132610305,1119961795,1128612806,1153892889,1111949977,1134052375,&
1888       1150633107,1141982096,1125008140,1141523721,1141392134,1124352898,&
1889       1140933825,1153647685,1137066695,  25575816,1108034316,1141654795,&
1890       1191659526,1225148935,1250577036/
1891  data (ichcod(j,2),j= 571,652) / 82 * 0 /
1892
1893  chstr(1)(61:61) = '\\'
1894  chstr(2)(59:59) = '\\'
1895  if (ifont .eq. 1)  then
1896     isel = 1
1897  elseif (ifont .eq. -13)  then
1898     isel = 2
1899  else
1900     ierr = 1
1901     goto 999
1902  endif
1903  ipos = index(chstr(isel)(:nchinf(isel)), ch)
1904  if (ipos .eq. 0)  then
1905     ierr = 2
1906  else
1907     ierr = 0
1908     iwid = 0
1909     np = 0
1910     istr = 0
1911     call cbyt(ichinf(ipos,isel), 19, iwid, 1, 6)
1912     width = 0.01 * iwid
1913     if (imode .ne. 0)  then
1914        call cbyt(ichinf(ipos,isel), 11, np, 1, 8)
1915        call cbyt(ichinf(ipos,isel),  1, istr, 1, 10)
1916        do i = 1, np
1917           k     = istr + i
1918           kword = k / 2
1919           kbit  = 17 - 16 * (k - 2 * kword)
1920           ipen(i) = 0
1921           call cbyt(ichcod(kword,isel), kbit, ipen(i), 1, 16)
1922           if (ipen(i) .ge. 16384)  then
1923              ip = 1
1924              ipen(i) = ipen(i) - 16384
1925           else
1926              ip = 0
1927           endif
1928           lx   = ipen(i) / 128
1929           x(i) = 0.01 * lx
1930           ly   = ipen(i) - 128 * lx
1931           if (ly .ge. 64)  then
1932              y(i) = 0.01 * (64 - ly)
1933           else
1934              y(i) = 0.01 * ly
1935           endif
1936           ipen(i) = ip
1937        enddo
1938     endif
1939  endif
1940999 end subroutine gxfchr
1941character(60) function gxform(string)
1942  implicit none
1943  integer i,ipt,kmant,l,n
1944  !
1945  !   creates the correct format for Input variables  contained  in  a
1946  !   character  variable  in  free format (blank characters acting as
1947  !   separators !). It accepts I,F,E,D,L, and A format variables, the
1948  !   latter  without  any  quotes,   being   just   those   character
1949  !   combinations  which  cannot  be  attributed  to any of the other
1950  !   formats.
1951  !
1952  !   gxform overcomes the short-coming of FORTRAN77 to not allow  free
1953  !   format  READ  statements  from  internal  files,  i.e. character
1954  !   variables.  If STRING is a character variable, then
1955  !
1956  !   read(strING,*)  N,A,etc.
1957  !
1958  !   is  not  legal  ANSI  FORTRAN  (although   supported   by   some
1959  !   compilers).  In this case one can use
1960  !
1961  !   read(strING,GXFORM(STRING))  N,A,etc.
1962  !
1963  !   which is legal. GXFORM has to be  declared  CHARACTER*60  in  the
1964  !   calling routine.
1965  !
1966  !   Input
1967  !   string    character type Input line
1968  !   Output
1969  !   gxform    FORMAT, e.g. (I4,A12,L4,F8.3,I3,E12.4,D24.8)
1970  !
1971  !   restrictions: the maximum length of the complete  format  is  60
1972  !   characters.
1973  !
1974  !   Author    HG      4.3.86   last mod.: 9.6.86
1975  !
1976  character string*(*),stemp*1,sfchar*1,form*80
1977  logical count,realfl,expfl,number
1978  form='(A1)'
1979  ipt=1
1980  n=1
1981  kmant=0
1982  realfl=.false.
1983  expfl=.false.
1984  count=.false.
1985  number=.false.
1986  sfchar='I'
1987  do i=1,len(string)
1988     if(ipt.ge.60) goto 20
1989     stemp=string(i:i)
1990     if(stemp.eq.' ') then
1991        if(count) then
1992           l=i-n
1993           ipt=ipt+1
1994           form(ipt:ipt)=sfchar
1995           if(l.ge.10) then
1996              write(form(ipt+1:),'(I2)') l
1997              ipt=ipt+2
1998           else
1999              write(form(ipt+1:),'(I1)') l
2000              ipt=ipt+1
2001           endif
2002           if(realfl.or.expfl)  then
2003              write(form(ipt+1:),'(I2)')  min(9,kmant)
2004              form(ipt+1:ipt+1)='.'
2005              ipt=ipt+2
2006           endif
2007           ipt=ipt+1
2008           form(ipt:ipt)=','
2009           n=i
2010           expfl=.false.
2011           realfl=.false.
2012           count=.false.
2013           number=.false.
2014           sfchar='I'
2015           kmant=0
2016        endif
2017     else
2018        if(.not.count) then
2019           !--- first character of a new variable
2020           if(stemp.eq.'.') then
2021              !--- could be floating, or logical
2022              if(index(string(i:),'.T.').eq.1.or.                       &
2023                   index(string(i:),'.F.').eq.1.or.                                  &
2024                   index(string(i:),'.TRUE.').eq.1.or.                               &
2025                   index(string(i:),'.FALSE.').eq.1) then
2026
2027                 sfchar='L'
2028              elseif(index('0123456789',string(i+1:i+1)).ne.0) then
2029                 number=.true.
2030              else
2031                 sfchar='A'
2032              endif
2033           elseif(index('+-0123456789',stemp).ne.0) then
2034              number=.true.
2035           else
2036              sfchar='A'
2037           endif
2038        endif
2039        count=.true.
2040        if(number) then
2041           if(stemp.eq.'E'.or.stemp.eq.'D') then
2042              expfl=.true.
2043              sfchar=stemp
2044           endif
2045           if(realfl.and..not.expfl) then
2046              kmant=kmant+1
2047              sfchar='F'
2048           endif
2049           realfl=realfl.or.stemp.eq.'.'
2050           if(realfl.and..not.expfl)  sfchar='F'
2051        endif
2052     endif
2053  enddo
2054  if(ipt.ge.4)  form(ipt:ipt)=')'
205520 gxform=form
2056end function gxform
2057subroutine gxfram(ncurv,nptval,ipxval,ipyval,icvref,xval,yval,window,ierr)
2058  use gxx11_common
2059  implicit none
2060  integer i,iaxr,iayr,ierr,j,jc,kset,ncurv
2061  real axpos,d,fx,fy
2062  !***********************************************************************
2063  !
2064  !   Purpose: plots one frame with several axes, returns GKS windows
2065  !
2066  !--- Input
2067  !   ncurv      number of curves (=ordered sets of (x,y) pairs) to plot
2068  !   nptval(i)  number of points ((x,y) pairs) in set I
2069  !   ipxval(i)  first x value of set I in array XVAL
2070  !   ipyval(i)  first y value of set I in array YVAL
2071  !   icvref(i)  number of the parameter set to be used for curve I. This value
2072  !            will be forced into [1,MAXSET].
2073  !            The x and y axis reference numbers of set I will be taken
2074  !            from this parameter set. All x and y axes with the
2075  !            corresponding reference numbers will be (scaled if automatic)
2076  !            and plotted together with set I.
2077  !            If no x resp. y axis exists with the reference number
2078  !            from the parameter set, the curve will be plotted with
2079  !            automatic scaling, but without x resp. y axis.
2080  !   xval       array containing the x values for all sets
2081  !   yval       array containing the y values for all sets
2082  !--- Output
2083  !   window(j,I) GKS window (J=1...4) to be used with curve I. These values
2084  !            are used by routine GXCURV
2085  !   ierr       0 if everything OK, else GKS error, or
2086  !            1 : GXINIT not called (initialization)
2087  !
2088  !   Author: H. Grote / CERN                        date: June 16, 1987
2089  !                                           last mod: May 13, 1993
2090  !
2091  !***********************************************************************
2092
2093  integer nptval(*),ipxval(*),ipyval(*),icvref(*)
2094  real xval(*),yval(*),window(4,*)
2095  integer ixax(mxaxs),iyax(myaxs),ixaref(maxset),iyaref(maxset),    &
2096       ilpar(30)
2097  real wn(4)
2098  !
2099  do i=1,30
2100     ilpar(i)=0
2101  enddo
2102  ierr=0
2103  !--- open .eps file if requested
2104  if (iepsop .lt. 0) call gxstep
2105  !--- set reasonable defaults for plot style
2106  call gxspmt
2107  !--- set axis flags to "not plotted"
2108  do i=1,mxaxs
2109     ixax(i)=0
2110  enddo
2111  do i=1,myaxs
2112     iyax(i)=0
2113  enddo
2114  !--- set axis curve references to "not set"
2115  do i=1,maxset
2116     ixaref(i)=0
2117     iyaref(i)=0
2118  enddo
2119  !--- get x and y axis reference numbers
2120  do i=1,ncurv
2121     kset=max(1,min(maxset,icvref(i)))
2122     ixaref(kset)=icvpar(1,kset)
2123     iyaref(kset)=icvpar(2,kset)
2124  enddo
2125  !--- get all window values for x
2126  call gxprwn(1,ncurv,icvref,nptval,ipxval,ipxval,xval,xval,        &
2127       mxaxs,ixaref,ixapar,rangex,axwndx)
2128  !--- get all window values for y
2129  call gxprwn(2,ncurv,icvref,nptval,ipxval,ipyval,xval,yval,        &
2130       myaxs,iyaref,iyapar,rangey,axwndy)
2131  !--- get the window in NDC into which the plot has to fit, depending on
2132  !   axis positions, labels, tick marks, etc.
2133  call gxmarg(ixaref,iyaref,axwndx,axwndy,actwnd)
2134  !--- identical x and y ratios if requested
2135  if(isqflg.gt.0)  then
2136     d=min(actwnd(2)-actwnd(1),actwnd(4)-actwnd(3))
2137     actwnd(2)=actwnd(1)+d
2138     actwnd(4)=actwnd(3)+d
2139  endif
2140  !--- set window factors
2141  fx=1./(actwnd(2)-actwnd(1))
2142  fy=1./(actwnd(4)-actwnd(3))
2143  !--- loop over curve sets, plot axes
2144  do kset=1,maxset
2145     iaxr=ixaref(kset)
2146     if(iaxr.eq.0) goto 100
2147     !--- get window according to margin
2148     wn(1)=(actwnd(2)*axwndx(1,kset)-actwnd(1)*axwndx(2,kset))*fx
2149     wn(2)=((1.-actwnd(1))*axwndx(2,kset)- (1.-actwnd(2))*axwndx     &
2150          (1,kset))*fx
2151     wn(3)=(actwnd(4)*axwndy(1,kset)-actwnd(3)*axwndy(2,kset))*fy
2152     wn(4)=((1.-actwnd(3))*axwndy(2,kset)- (1.-actwnd(4))*axwndy     &
2153          (1,kset))*fy
2154     call jswn(inormt,wn(1),wn(2),wn(3),wn(4))
2155     !     call jselnt(inormt)
2156     !--- keep
2157     do j=1,4
2158        window(j,kset)=wn(j)
2159     enddo
2160     !--- plot x axes
2161     do i=1,mxaxs
2162        if(ixapar(21,i).eq.iaxr) then
2163           if(ixax(i).eq.0) then
2164              ixax(i)=1
2165              !--- x axis no. 1 and 2 at bottom, 3 and 4 at top of frame
2166              if(i.le.2) then
2167                 axpos=axwndy(1,kset)
2168              else
2169                 axpos=axwndy(2,kset)
2170              endif
2171              !--- set parameters, get interval number if scaling automatic
2172              do jc=1,mpaxs
2173                 ilpar(jc)=ixapar(jc,i)
2174              enddo
2175              ilpar(2)=ixapar(19,i)
2176              call gxaxis('X',axwndx(1,kset), axwndx(2,kset),axpos,     &
2177                   1,sxform(i),sxtext(i),sdefnl,ilpar,ierr)
2178              if(ierr.ne.0) goto 999
2179           endif
2180        endif
2181     enddo
2182     !--- plot y axes
2183     iayr=iyaref(kset)
2184     do i=1,myaxs
2185        if(iyapar(21,i).eq.iayr) then
2186           if(iyax(i).eq.0) then
2187              iyax(i)=1
2188              !--- y axis 1 at left,annotation at left, 2 at left, ann. at right,
2189              !   3 at right, ann. at left, 4 at right, ann. at right
2190              if(i.le.2) then
2191                 axpos=axwndx(1,kset)
2192              else
2193                 axpos=axwndx(2,kset)
2194              endif
2195              !--- set parameters, get interval number if scaling automatic
2196              do jc=1,mpaxs
2197                 ilpar(jc)=iyapar(jc,i)
2198              enddo
2199              ilpar(2)=iyapar(19,i)
2200              call gxaxis('Y',axwndy(1,kset),axwndy(2,kset), axpos,     &
2201                   1,syform(i), sytext(i),sdefnl,ilpar,ierr)
2202
2203              if(ierr.ne.0) goto 999
2204           endif
2205        endif
2206     enddo
2207100  continue
2208  enddo
2209999 end subroutine gxfram
2210subroutine gxfrm1(ncurv,nptval,ipxval,ipyval,icvref,xval,yval,window,actwin,ierr)
2211  use gxx11_common
2212  implicit none
2213  integer i,iaxr,iayr,ierr,j,jc,kset,ncurv
2214  !***********************************************************************
2215  !
2216  !   Purpose: plots one frame with several axes, returns GKS and active
2217  !         windows.
2218  !
2219  !--- Input
2220  !   ncurv      number of curves (=ordered sets of (x,y) pairs) to plot
2221  !   nptval(i)  number of points ((x,y) pairs) in set I
2222  !   ipxval(i)  first x value of set I in array XVAL
2223  !   ipyval(i)  first y value of set I in array YVAL
2224  !   icvref(i)  number of the parameter set to be used for curve I. This value
2225  !            will be forced into [1,MAXSET].
2226  !            The x and y axis reference numbers of set I will be taken
2227  !            from this parameter set. All x and y axes with the
2228  !            corresponding reference numbers will be (scaled if automatic)
2229  !            and plotted together with set I.
2230  !            If no x resp. y axis exists with the reference number
2231  !            from the parameter set, the curve will be plotted with
2232  !            automatic scaling, but without x resp. y axis.
2233  !   xval       array containing the x values for all sets
2234  !   yval       array containing the y values for all sets
2235  !--- Output
2236  !   window(j,I) GKS window (J=1...4) to be used with curve I. These values
2237  !            are used by routines GXCURV and GXCRV1.
2238  !   actwin(j,I) active window (J=1...4) used to clip curve I. These values
2239  !            are used by routine GXCRV1.
2240  !   ierr       0 if everything OK, else GKS error, or
2241  !            1 : GXINIT not called (initialization)
2242  !
2243  !   Author: H. Grote / CERN                        date: Dec. 9, 1988
2244  !                                           last mod: May 13, 1993
2245  !
2246  !***********************************************************************
2247
2248  integer nptval(*),ipxval(*),ipyval(*),icvref(*)
2249  real xval(*),yval(*),window(4,*),actwin(4,*)
2250  integer ixax(mxaxs),iyax(myaxs),ixaref(maxset),iyaref(maxset),    &
2251       ilpar(30)
2252  real wn(4),axpos,d,fx,fy
2253  !
2254  do i=1,30
2255     ilpar(i)=0
2256  enddo
2257  ierr=0
2258  !--- open .eps file if requested
2259  if (iepsop .lt. 0) call gxstep
2260  !--- set reasonable defaults for plot style
2261  call gxspmt
2262  !--- set axis flags to "not plotted"
2263  do i=1,mxaxs
2264     ixax(i)=0
2265  enddo
2266  do i=1,myaxs
2267     iyax(i)=0
2268  enddo
2269  !--- set axis curve references to "not set"
2270  do i=1,maxset
2271     ixaref(i)=0
2272     iyaref(i)=0
2273  enddo
2274  !--- get x and y axis reference numbers
2275  do i=1,ncurv
2276     kset=max(1,min(maxset,icvref(i)))
2277     ixaref(kset)=icvpar(1,kset)
2278     iyaref(kset)=icvpar(2,kset)
2279  enddo
2280  !--- get all window values for x
2281  call gxprwn(1,ncurv,icvref,nptval,ipxval,ipxval,xval,xval,        &
2282       mxaxs,ixaref,ixapar,rangex,axwndx)
2283  !--- get all window values for y
2284  call gxprwn(2,ncurv,icvref,nptval,ipxval,ipyval,xval,yval,        &
2285       myaxs,iyaref,iyapar,rangey,axwndy)
2286  !--- get the window in NDC into which the plot has to fit, depending on
2287  !   axis positions, labels, tick marks, etc.
2288  call gxmarg(ixaref,iyaref,axwndx,axwndy,actwnd)
2289  !--- identical x and y ratios if requested
2290  if(isqflg.gt.0)  then
2291     d=min(actwnd(2)-actwnd(1),actwnd(4)-actwnd(3))
2292     actwnd(2)=actwnd(1)+d
2293     actwnd(4)=actwnd(3)+d
2294  endif
2295  !--- set window factors
2296  fx=1./(actwnd(2)-actwnd(1))
2297  fy=1./(actwnd(4)-actwnd(3))
2298  !--- loop over curve sets, plot axes
2299  do kset=1,maxset
2300     iaxr=ixaref(kset)
2301     if(iaxr.eq.0) goto 100
2302     !--- get window according to margin
2303     wn(1)=(actwnd(2)*axwndx(1,kset)-actwnd(1)*axwndx(2,kset))*fx
2304     wn(2)=((1.-actwnd(1))*axwndx(2,kset)- (1.-actwnd(2))*axwndx     &
2305          (1,kset))*fx
2306     wn(3)=(actwnd(4)*axwndy(1,kset)-actwnd(3)*axwndy(2,kset))*fy
2307     wn(4)=((1.-actwnd(3))*axwndy(2,kset)- (1.-actwnd(4))*axwndy     &
2308          (1,kset))*fy
2309     call jswn(inormt,wn(1),wn(2),wn(3),wn(4))
2310     !     call jselnt(inormt)
2311     !--- keep
2312     do j=1,4
2313        window(j,kset)=wn(j)
2314     enddo
2315     !--- active window in user coordiantes
2316     actwin(1,kset)=wn(1)+(wn(2)-wn(1))*actwnd(1)
2317     actwin(2,kset)=wn(1)+(wn(2)-wn(1))*actwnd(2)
2318     actwin(3,kset)=wn(3)+(wn(4)-wn(3))*actwnd(3)
2319     actwin(4,kset)=wn(3)+(wn(4)-wn(3))*actwnd(4)
2320     !--- plot x axes
2321     do i=1,mxaxs
2322        if(ixapar(21,i).eq.iaxr) then
2323           if(ixax(i).eq.0) then
2324              ixax(i)=1
2325              !--- x axis no. 1 and 2 at bottom, 3 and 4 at top of frame
2326              if(i.le.2) then
2327                 axpos=axwndy(1,kset)
2328              else
2329                 axpos=axwndy(2,kset)
2330              endif
2331              !--- set parameters, get interval number if scaling automatic
2332              do jc=1,mpaxs
2333                 ilpar(jc)=ixapar(jc,i)
2334              enddo
2335              ilpar(2)=ixapar(19,i)
2336              call gxaxis('X',axwndx(1,kset), axwndx(2,kset),axpos,     &
2337                   1,sxform(i),sxtext(i),sdefnl,ilpar,ierr)
2338              if(ierr.ne.0) goto 999
2339           endif
2340        endif
2341     enddo
2342     !--- plot y axes
2343     iayr=iyaref(kset)
2344     do i=1,myaxs
2345        if(iyapar(21,i).eq.iayr) then
2346           if(iyax(i).eq.0) then
2347              iyax(i)=1
2348              !--- y axis 1 at left,annotation at left, 2 at left, ann. at right,
2349              !   3 at right, ann. at left, 4 at right, ann. at right
2350              if(i.le.2) then
2351                 axpos=axwndx(1,kset)
2352              else
2353                 axpos=axwndx(2,kset)
2354              endif
2355              !--- set parameters, get interval number if scaling automatic
2356              do jc=1,mpaxs
2357                 ilpar(jc)=iyapar(jc,i)
2358              enddo
2359              ilpar(2)=iyapar(19,i)
2360              call gxaxis('Y',axwndy(1,kset),axwndy(2,kset), axpos,     &
2361                   1,syform(i), sytext(i),sdefnl,ilpar,ierr)
2362
2363              if(ierr.ne.0) goto 999
2364           endif
2365        endif
2366     enddo
2367100  continue
2368  enddo
2369999 end subroutine gxfrm1
2370subroutine gxinit
2371  use gxx11_common
2372  implicit none
2373  integer idummy,ierr
2374  !***********************************************************************
2375  !
2376  !   Purpose: initializes GKS PLOT package
2377  !
2378  !   the default is to open the plot package for metafile writing only.
2379  !   the corresponding parameters (unit number, file name, status, paper
2380  !   width and length) can be set by calls to gxsvar beforehand.
2381  !
2382  !   for interactive usage (plot Output on screen) it is mandatory to
2383  !   call gxaSKU before calling GXINIT. Parameters can be modified after
2384  !   the gxasKU call (but before the GXINIT call) by calling gxsvar.
2385  !
2386  !   Author: H. Grote / CERN                        date: June 16, 1987
2387  !                                           last mod: June 16, 1987
2388  !
2389  !***********************************************************************
2390
2391  if (ltotin .ne. lundef)  then
2392     print '(/'' GXPLOT-X11 '',F5.2,'' initialized''/)',versio
2393  endif
2394  !--- reset open flag for .eps files
2395  iepsop = 0
2396  iepscf = 0
2397  iclear = 0
2398  ipage = 0
2399  call wopks(ierrun, idummy)
2400  call gxundf
2401  !--- set default options
2402  call gxsdef('OPTINIT',0)
2403  if(interm.ne.0)  then
2404     itermt = 1
2405  else
2406     itermt = 0
2407  endif
2408  if (ltseop .ne. lundef .or. itseop .eq. 0)  then
2409     if (itermt .ne. 0)  call wopwk(interm, mconid, itermt)
2410  endif
2411  wxfact=1.
2412  wyfact=1.
2413  wfact=1.
2414  if(inmeta .ne. 0)  then
2415     !--- orientation (portrait or landscape)
2416     if (xmetaf .gt. ymetaf) then
2417        ipstyp = 115
2418     else
2419        ipstyp = 114
2420     endif
2421     iorips = ipstyp - 113
2422     ibbox(1) = mlbb1
2423     ibbox(2) = mlbb2
2424     ibbox(3) = mubb1
2425     ibbox(4) = mubb2
2426     if (xmetaf .gt. 0.)  then
2427        if (iorips .eq. 1)  then
2428           ibbox(3) = mlbb1 + mwid1 * xmetaf / mysize + 0.5
2429        else
2430           ibbox(4) = mlbb2 + mwid2 * xmetaf / mxsize + 0.5
2431        endif
2432     endif
2433     if (ymetaf .gt. 0.)  then
2434        if (iorips .eq. 1)  then
2435           ibbox(4) = mlbb2 + mwid2 * ymetaf / mxsize + 0.5
2436        else
2437           ibbox(3) = mlbb1 + mwid1 * ymetaf / mysize + 0.5
2438        endif
2439     endif
2440     if (interm .eq. 0)  then
2441        imetun = -abs(imetun)
2442     endif
2443     if (lpseps .ne. lundef)  then
2444        ipseps = 1
2445        lpseps = lundef
2446     endif
2447     if (ipseps .eq. 1)  then
2448        if(lmetop.ne.lundef)  call gxsfop('PSFILE','UNKNOWN',ierr)
2449        call gxopps(imetun, ipstyp)
2450     elseif (ipseps .eq. 2)  then
2451        ipstyp = 113
2452        iepsop = -2
2453     endif
2454  endif
2455  !--- activate workstations
2456  if (ltseop .ne. lundef .or. itseop .eq. 0)  then
2457     if(interm.gt.0) then
2458        call wacwk(interm)
2459        lacttm=lundef
2460     endif
2461  endif
2462  !--- set default window and viewport, aspect source flags,
2463  !   norm. transf. number
2464  call gxsdef('DEVICE',0)
2465  !--- axis default values
2466  call gxsdef('AXIS',0)
2467  !--- curve defaults
2468  call gxsdef('CURVE',0)
2469  !--- set flag that GXINIT has been called
2470  ltotin=lundef
247110000 format(//' GKS error number =',i4,' returned for terminal',       &
2472       ' device =',i8,'  STOP')
2473end subroutine gxinit
2474subroutine gxival(string,ivalex)
2475  implicit none
2476  integer i,ifnd,ivalex,n
2477  !***********************************************************************
2478  !
2479  !   Purpose: extracts a positive integer from a string
2480  !
2481  !--- Input
2482  !   string    arbitrary character string
2483  !--- Output
2484  !   ivalex    first integer found in string (terminated by any
2485  !           non-numeric character, including blank)
2486  !   Author: H. Grote / CERN                        date: June 16, 1987
2487  !                                           last mod: Sept. 8, 1987
2488  !
2489  !***********************************************************************
2490  character(*) string
2491  character snumer*10
2492  save snumer
2493  data snumer/'0123456789'/
2494  ivalex=0
2495  ifnd=0
2496  do i=1,len(string)
2497     n=index(snumer,string(i:i))
2498     if(n.eq.0) then
2499        if(ifnd.ne.0) goto 999
2500     else
2501        ifnd=1
2502        ivalex=10*ivalex+n-1
2503     endif
2504  enddo
2505999 end subroutine gxival
2506subroutine gxmarg(ixref,iyref,wnx,wny,active)
2507  use gxx11_common
2508  implicit none
2509  integer i,iax,iaxr,ifirst,ilast,ind,intv,iscal,ival,j,k,kset,nax, &
2510       nchct,nint,nref
2511  real add,ahi,alo,fact,gap,gapt,hgap,hgapt,hwid,hwidt,txf,vgap,    &
2512       vgapt,vwid,vwidt,xf
2513  !***********************************************************************
2514  !
2515  !   Purpose: calculates window margins from axes specifications
2516  !
2517  !--- Input
2518  !   ixref      x axis reference numbers of curve sets
2519  !   iyref      y axis reference numbers of curve sets
2520  !   wnx(2,i)   lower and upper x value, curve set I
2521  !   wny(2,i)   lower and upper y value, curve set I
2522  !--- Output
2523  !   active     (1...4) = window in NDC that can be used for curves
2524  !
2525  !   Author: H. Grote / CERN                        date: June 16, 1987
2526  !                                           last mod: March 3, 1988
2527  !
2528  !***********************************************************************
2529
2530  integer ixref(*),iyref(*)
2531  real wnx(2,*),wny(2,*)
2532  real active(4),bmin(2)
2533  integer iref(mxaxs+myaxs),iapar(mpaxs)
2534  real border(4)
2535  logical flag
2536  character fmt*20,text*300,fmtloc*60
2537  save fact
2538  !--- fact includes one character height plus the gap of half that height
2539  data fact/.0015/
2540  !--- get viewport ratio
2541  call gxqrvp(xf)
2542  do i=1,4
2543     border(i)=0.
2544  enddo
2545  do i=1,2
2546     bmin(i)=0.
2547  enddo
2548  do iax=1,2
2549     nref=0
2550     do kset=1,maxset
2551        if(iax.eq.1) then
2552           !--- x axis
2553           iaxr=ixref(kset)
2554        else
2555           !--- y axis
2556           iaxr=iyref(kset)
2557        endif
2558        if(iaxr.eq.0) goto 70
2559        do j=1,nref
2560           if(iaxr.eq.iref(j)) goto 70
2561        enddo
2562        nref=nref+1
2563        iref(nref)=iaxr
2564        if(iax.eq.1) then
2565           nax=mxaxs
2566        else
2567           nax=myaxs
2568        endif
2569        do i=1,nax
2570           add=0.
2571           if(iax.eq.1) then
2572              !--- x axis
2573              if(iaxr.ne.ixapar(21,i)) goto 60
2574              ind=(4-i)/2
2575              k=4-ind
2576              fmt=sxform(i)
2577              text=sxtext(i)
2578              !--- tick mark expansion
2579              txf=1.
2580              do j=1,mpaxs
2581                 iapar(j)=ixapar(j,i)
2582              enddo
2583           else
2584              !--- y axis
2585              if(iaxr.ne.iyapar(21,i)) goto 60
2586              ind=(4-i)/2
2587              k=2-ind
2588              fmt=syform(i)
2589              text=sytext(i)
2590              !--- tick mark expansion
2591              txf=xf
2592              do j=1,mpaxs
2593                 iapar(j)=iyapar(j,i)
2594              enddo
2595           endif
2596           gap=fact*iapar(7)
2597           !--- use separate character height for axis text if specified
2598           if(iapar(13).gt.0.and.iapar(13).le.1000)  then
2599              gapt=fact*iapar(13)
2600           else
2601              gapt=gap
2602           endif
2603           !--- get character height and width for hor. and vert. text
2604           call gxschf(0,1,gap,hgap,hwid)
2605           call gxschf(0,2,gap,vgap,vwid)
2606           call gxschf(0,1,gapt,hgapt,hwidt)
2607           call gxschf(0,2,gapt,vgapt,vwidt)
2608           !--- tick marks
2609           if(iapar(2).ne.0.and.iapar(4).ne.0) then
2610              if(mod(iapar(4),2).eq.ind) add=add+txf*fact*iapar(8)
2611           endif
2612           !--- labels
2613           if(iapar(3).ne.0.and.iapar(5).ne.0) then
2614              flag=mod(iapar(5),2).eq.ind
2615              if(iapar(1).eq.0)  then
2616                 !--- linear scale - use format if given by user, else calculate
2617                 call gxival(fmt,ival)
2618                 if(ival.eq.0) then
2619                    if(iax.eq.1)  then
2620                       call gxscal(wnx(1,kset),wnx(2,kset),alo,ahi,        &
2621                            nint)
2622                    else
2623                       call gxscal(wny(1,kset),wny(2,kset),alo,ahi,        &
2624                            nint)
2625                    endif
2626                    intv = iapar(2)
2627                    if (intv .le. 0)  call gxdint(alo,ahi,intv)
2628                    call gxdfmt(alo,ahi,intv,ival,iscal,fmtloc)
2629                 endif
2630              else
2631                 !--- log. scale - use powers of 10
2632                 ival=5
2633              endif
2634              if(iax.eq.iapar(3)) then
2635                 !--- labels parallel to axis
2636                 if(iax.eq.1) then
2637                    if(flag) add=add+hgap
2638                    !--- keep minimum border for labels on perpendicular axes
2639                    bmin(iax)=max(bmin(iax),.5*ival*hwid)
2640                 else
2641                    if(flag) add=add+vgap
2642                    bmin(iax)=max(bmin(iax),.5*ival*vwid)
2643                 endif
2644              else
2645                 !--- labels perpendicular to axis
2646                 if(iax.eq.1) then
2647                    if(flag) add=add+ival*vwid
2648                    !--- keep minimum border for labels on perpendicular axes
2649                    bmin(iax)=max(bmin(iax),.5*vgap)
2650                 else
2651                    if(flag) add=add+ival*hwid
2652                    !--- keep minimum border for labels on perpendicular axes
2653                    bmin(iax)=max(bmin(iax),.5*hgap)
2654                 endif
2655              endif
2656           endif
2657           !--- text - always parallel to axis
2658           call gxpnbl(text,ifirst,ilast)
2659           if(iapar(6).ne.0.and.mod(iapar(6),2).eq.ind                 &
2660                .and.ifirst.ne.0)  then
2661              !--- add space for one line and extra space for each line separator
2662              call gxchct(text(ifirst:ilast),sdefnl,nchct)
2663              if(iax.eq.1) then
2664                 add=add+(nchct+1)*hgapt
2665                 if(i.ge.3) add=add+.5*hgapt
2666              else
2667                 add=add+(nchct+1)*vgapt
2668              endif
2669           endif
2670           !--- take largest margin
2671           border(k)=max(border(k),add)
267260         continue
2673        enddo
267470      continue
2675     enddo
2676  enddo
2677  do i=1,3,2
2678     active(i)=max(border(i),bmin((i+1)/2))
2679     active(i+1)=1.-max(border(i+1),bmin((i+1)/2))
2680     !--- protect against too large borders
2681     if(active(i).ge.active(i+1))  then
2682        active(i)=.4
2683        active(i+1)=.6
2684     endif
2685  enddo
2686999 end subroutine gxmarg
2687subroutine gxopen
2688  use gxx11_common
2689  implicit none
2690  !***********************************************************************
2691  !
2692  !   Purpose: open  terminal workstation
2693  !
2694  !   Author: H. Grote / CERN                        date: Feb. 26, 1988
2695  !                                           last mod: Feb. 26, 1988
2696  !
2697  !***********************************************************************
2698
2699  call gxundf
2700  if(lacttm.ne.lundef)  then
2701     if(interm.gt.0)  then
2702        call wopwk(interm, mconid, itermt)
2703        call wacwk(interm)
2704        lacttm=lundef
2705     endif
2706     call gxclrw
2707  endif
2708end subroutine gxopen
2709subroutine gxopps(iun, ityp)
2710  use gxx11_common
2711  implicit none
2712  integer imun,ityp,iun
2713  !***********************************************************************
2714  !
2715  !   Purpose: open or close .ps or .eps Output unit
2716  !
2717  !--- Input
2718  !   iun       +- utput unit number, if = 0: close
2719  !   ityp      type of Output: 113 = eps,
2720  !           else ps with 114 = portrait, 115 = landscape
2721  !
2722  !   Author: H. Grote / CERN                        date: Apr.  6, 1995
2723  !                                           last mod: Apr. 27, 1995
2724  !
2725  !***********************************************************************
2726
2727  imun = abs(iun)
2728  call gxwpep(imun, ityp)
2729end subroutine gxopps
2730subroutine gxplot(ncurv,nptval,ipxval,ipyval,icvref,xval,yval,ierr)
2731  use gxx11_common
2732  implicit none
2733  integer ierr,ncurv
2734  !***********************************************************************
2735  !
2736  !   Purpose: plots one frame with several curves and axes
2737  !
2738  !--- Input
2739  !   ncurv      number of curves (=ordered sets of (x,y) pairs) to plot
2740  !   nptval(i)  number of points ((x,y) pairs) in set I
2741  !   ipxval(i)  first x value of set I in array XVAL
2742  !   ipyval(i)  first y value of set I in array YVAL
2743  !   icvref(i)  number of the parameter set to be used for curve I. This value
2744  !            will be forced into [1,MAXSET].
2745  !            The x and y axis reference numbers of set I will be taken
2746  !            from this parameter set. All x and y axes with the
2747  !            corresponding reference numbers will be (scaled if automatic)
2748  !            and plotted together with set I.
2749  !            If no x resp. y axis exists with the reference number
2750  !            from the parameter set, the curve will be plotted with
2751  !            automatic scaling, but without x resp. y axis.
2752  !   xval       array containing the x values for all sets
2753  !   yval       array containing the y values for all sets
2754  !--- Output
2755  !   ierr       0 if everything OK, else GKS error, or
2756  !            1 : GXINIT not called (initialization)
2757  !
2758  !   Author: H. Grote / CERN                        date: June 16, 1987
2759  !                                           last mod: June 16, 1987
2760  !
2761  !***********************************************************************
2762
2763  integer nptval(*),ipxval(*),ipyval(*),icvref(*)
2764  real xval(*),yval(*)
2765  !
2766  call gxundf
2767  !--- exit if not initialized
2768  if(ltotin.ne.lundef)  then
2769     ierr=1
2770     goto 999
2771  endif
2772  !--- clear work station(s) if requested
2773  if(iclflg.gt.0)  call gxclrw
2774  !--- plot frame
2775  call gxfram(ncurv,nptval,ipxval,ipyval,icvref,xval,yval,          &
2776       cvwnwd,ierr)
2777  !--- plot curves
2778  call gxcurv(ncurv,nptval,ipxval,ipyval,icvref,xval,yval,          &
2779       cvwnwd,ierr)
2780  !
2781  !--- wait for <CR> if interactive
2782  !
2783  call gxwait
2784999 end subroutine gxplot
2785subroutine gxplts(np,xp1,yp1)
2786  use gxx11_common
2787  implicit none
2788  integer i,ierror,j,k,nextra,np
2789  real d,gxcubv,screen,selem,sg,sl,step,xmax,xmin
2790  !***********************************************************************
2791  !
2792  !   Purpose: plots a smoothed polyline (3rd order cubic splines)
2793  !
2794  !--- Input
2795  !   np         number of points
2796  !   xp1        x values
2797  !   yp1        y values
2798  !
2799  !   Author: H. Grote / CERN                        date: June 16, 1987
2800  !                                           last mod: May 13, 1993
2801  !
2802  !***********************************************************************
2803  real xp1(*),yp1(*)
2804
2805  logical curlfl
2806  save screen, selem
2807  !--- screen is the dimension of a reasonable screen, SELEM the length
2808  !   of a curve piece such that it looks smooth
2809  data screen/30./, selem/.2/
2810  !
2811  if(np.le.2.or.np.gt.madim1) goto 70
2812  xmin=xp1(1)
2813  xmax=xp1(1)
2814  curlfl=.false.
2815  sg=sign(1.,xp1(2)-xp1(1))
2816  do i=2,np
2817     curlfl=curlfl.or.sg*xp1(i).le.sg*xp1(i-1)
2818     xmin=min(xmin,xp1(i))
2819     xmax=max(xmax,xp1(i))
2820  enddo
2821  if(xmax.eq.xmin) goto 999
2822  if(curlfl)  then
2823     !--- y is not a unique function of x - spline x and y independetly
2824     !   as function of s
2825     s(1)=0.
2826     do i=2,np
2827        s(i)=s(i-1)+sqrt((xp1(i)-xp1(i-1))**2+(yp1(i)-yp1(i-1))**2)
2828     enddo
2829     !--- step at which extra points should occur
2830     step=s(np)*selem/screen
2831     call gxcubi(np,s,xp1,yy1d(1,1),yy2d(1,1),ierror)
2832     if(ierror.ne.0) goto 70
2833     call gxcubi(np,s,yp1,yy1d(1,2),yy2d(1,2),ierror)
2834     if(ierror.ne.0) goto 70
2835     k=1
2836     p(1,1)=xp1(1)
2837     p(1,2)=yp1(1)
2838     do i=2,np
2839        !--- number of extra points to be plotted
2840        nextra=(s(i)-s(i-1))/step
2841        d=(s(i)-s(i-1))/(nextra+1)
2842        do j=1,nextra
2843           k=k+1
2844           sl=s(i-1)+j*d
2845           p(k,1)=gxcubv(sl,np,s,xp1,yy1d(1,1),yy2d(1,1))
2846           p(k,2)=gxcubv(sl,np,s,yp1,yy1d(1,2),yy2d(1,2))
2847        enddo
2848        k=k+1
2849        p(k,1)=xp1(i)
2850        p(k,2)=yp1(i)
2851     enddo
2852  else
2853     !--- step at which extra points should occur
2854     step=(xmax-xmin)*selem/screen
2855     call gxcubi(np,xp1,yp1,yy1d,yy2d,ierror)
2856     if(ierror.ne.0) goto 70
2857     k=1
2858     p(1,1)=xp1(1)
2859     p(1,2)=yp1(1)
2860     do i=2,np
2861        !--- number of extra points to be plotted
2862        nextra=abs(xp1(i)-xp1(i-1))/step
2863        d=(xp1(i)-xp1(i-1))/(nextra+1)
2864        do j=1,nextra
2865           k=k+1
2866           p(k,1)=xp1(i-1)+j*d
2867           p(k,2)=gxcubv(p(k,1),np,xp1,yp1,yy1d,yy2d)
2868        enddo
2869        k=k+1
2870        p(k,1)=xp1(i)
2871        p(k,2)=yp1(i)
2872     enddo
2873  endif
2874  call gvpl(k,p(1,1),p(1,2))
2875  goto 999
287670 continue
2877  !
2878  !--- error condition - not enough, too many, or identical points
2879  !
2880  call gvpl(np,xp1,yp1)
2881999 end subroutine gxplts
2882subroutine gxplt1(np,xp1,yp1,ac)
2883  use gxx11_common
2884  implicit none
2885  integer i,ierror,j,k,nextra,np
2886  real d,gxcubv,screen,selem,sg,sl,step,xmax,xmin
2887  !***********************************************************************
2888  !
2889  !   Purpose: plots a smoothed polyline (3rd order cubic splines), clips
2890  !
2891  !--- Input
2892  !   np         number of points
2893  !   xp1         x values
2894  !   yp1         y values
2895  !   ac         active window for clipping ---> routine GXPL
2896  !
2897  !   Author: H. Grote / CERN                        date: Dec. 9, 1988
2898  !                                           last mod: May 13, 1993
2899  !
2900  !***********************************************************************
2901  real xp1(*),yp1(*),ac(4)
2902
2903  logical curlfl
2904  save screen, selem
2905  !--- screen is the dimension of a reasonable screen, SELEM the length
2906  !   of a curve piece such that it looks smooth
2907  data screen/30./, selem/.2/
2908  !
2909  if(np.le.2.or.np.gt.madim1) goto 70
2910  xmin=xp1(1)
2911  xmax=xp1(1)
2912  curlfl=.false.
2913  sg=sign(1.,xp1(2)-xp1(1))
2914  do i=2,np
2915     curlfl=curlfl.or.sg*xp1(i).le.sg*xp1(i-1)
2916     xmin=min(xmin,xp1(i))
2917     xmax=max(xmax,xp1(i))
2918  enddo
2919  if(xmax.eq.xmin) goto 999
2920  if(curlfl)  then
2921     !--- y is not a unique function of x - spline x and y independetly
2922     !   as function of s
2923     s(1)=0.
2924     do i=2,np
2925        s(i)=s(i-1)+sqrt((xp1(i)-xp1(i-1))**2+(yp1(i)-yp1(i-1))**2)
2926     enddo
2927     !--- step at which extra points should occur
2928     step=s(np)*selem/screen
2929     call gxcubi(np,s,xp1,yy1d(1,1),yy2d(1,1),ierror)
2930     if(ierror.ne.0) goto 70
2931     call gxcubi(np,s,yp1,yy1d(1,2),yy2d(1,2),ierror)
2932     if(ierror.ne.0) goto 70
2933     k=1
2934     p(1,1)=xp1(1)
2935     p(1,2)=yp1(1)
2936     do i=2,np
2937        !--- number of extra points to be plotted
2938        nextra=(s(i)-s(i-1))/step
2939        d=(s(i)-s(i-1))/(nextra+1)
2940        do j=1,nextra
2941           k=k+1
2942           sl=s(i-1)+j*d
2943           p(k,1)=gxcubv(sl,np,s,xp1,yy1d(1,1),yy2d(1,1))
2944           p(k,2)=gxcubv(sl,np,s,yp1,yy1d(1,2),yy2d(1,2))
2945        enddo
2946        k=k+1
2947        p(k,1)=xp1(i)
2948        p(k,2)=yp1(i)
2949     enddo
2950  else
2951     !--- step at which extra points should occur
2952     step=(xmax-xmin)*selem/screen
2953     call gxcubi(np,xp1,yp1,yy1d,yy2d,ierror)
2954     if(ierror.ne.0) goto 70
2955     k = 1
2956     p(1,1)=xp1(1)
2957     p(1,2)=yp1(1)
2958     do i=2,np
2959        !--- number of extra points to be plotted
2960        nextra=abs(xp1(i)-xp1(i-1))/step
2961        d=(xp1(i)-xp1(i-1))/(nextra+1)
2962        do j=1,nextra
2963           k=k+1
2964           p(k,1)=xp1(i-1)+j*d
2965           p(k,2)=gxcubv(p(k,1),np,xp1,yp1,yy1d,yy2d)
2966        enddo
2967        if (k .eq. madim1)  then
2968           !--- flush buffer
2969           call gxpl(k, p(1,1), p(1,2), ac)
2970           p(1,1) = p(k,1)
2971           p(1,2) = p(k,2)
2972           k = 1
2973        endif
2974        k=k+1
2975        p(k,1)=xp1(i)
2976        p(k,2)=yp1(i)
2977     enddo
2978  endif
2979  if (k .gt. 1)  call gxpl(k,p(1,1),p(1,2),ac)
2980  goto 999
298170 continue
2982  !
2983  !--- error condition - not enough, too many, or identical points
2984  !
2985  call gxpl(np,xp1,yp1,ac)
2986999 end subroutine gxplt1
2987subroutine gxpl(n,x,y,ac)
2988  use gxx11_common
2989  implicit none
2990  integer i,ilow,j,k,n
2991  real xtol,ytol
2992  !***********************************************************************
2993  !
2994  !   Purpose: plots a polyline, clips at active window.
2995  !
2996  !--- Input:
2997  !   n          no. of points
2998  !   x          x positions
2999  !   y          y positions
3000  !   ac         active window
3001  !
3002  !   Author: H. Grote / CERN                        date: Dec. 9, 1988
3003  !                                           last mod: Dec. 9, 1988
3004  !
3005  !***********************************************************************
3006  real x(*),y(*),ac(4)
3007
3008  xtol = toleps * (ac(2) - ac(1))
3009  ytol = toleps * (ac(4) - ac(3))
3010  if (n .gt. 1)  then
3011     ilow = 1
301210   continue
3013     do  i = ilow, n
3014        if(x(i) + xtol .lt. ac(1))  goto 30
3015        if(x(i) - xtol .gt. ac(2))  goto 30
3016        if(y(i) + ytol .lt. ac(3))  goto 30
3017        if(y(i) - ytol .gt. ac(4))  goto 30
3018     enddo
301930   continue
3020     if (i - 1 .gt. ilow)  then
3021        call gvpl(i - ilow, x(ilow), y(ilow))
3022     endif
3023     do  j = max(i, 2), n
3024        call gxplxx(x(j-1),y(j-1), ac, xp, yp, k)
3025        if (k .eq. 2)  then
3026           call gvpl(2, xp, yp)
3027        endif
3028        if(x(j) + xtol .lt. ac(1))  goto 40
3029        if(x(j) - xtol .gt. ac(2))  goto 40
3030        if(y(j) + ytol .lt. ac(3))  goto 40
3031        if(y(j) - ytol .gt. ac(4))  goto 40
3032        ilow = j
3033        goto 10
303440      continue
3035     enddo
3036  endif
3037end subroutine gxpl
3038subroutine gxplxx(xin, yin, ac, xout,yout, kp)
3039  implicit none
3040  integer i,j,k,kp
3041  real t,xc,xtol,yc,ytol
3042  !***********************************************************************
3043  !
3044  !   Purpose: returns two points inside or on border of active window
3045  !
3046  !--- Input:
3047  !   xin        x positions of Input points
3048  !   yin        y positions of Input points
3049  !   ac         active window
3050  !--- Output
3051  !   xout       x positions of Output points
3052  !   yout       y positions of Output points
3053  !   kp         no. of points to plot (2 if OK, else less)
3054  !
3055  !   Author: H. Grote / CERN                        date: Dec. 9, 1988
3056  !                                           last mod: Dec. 3, 1992
3057  !
3058  !***********************************************************************
3059  real toleps
3060  parameter (toleps = 1.e-5)
3061  real ac(4), xin(2), yin(2), xout(2), yout(2)
3062  real x(2), y(2), xr(4), yr(4)
3063
3064  xtol = toleps * (ac(2) - ac(1))
3065  ytol = toleps * (ac(4) - ac(3))
3066  kp = 0
3067  do  i = 1, 2
3068     if(xin(i) + xtol .lt. ac(1))  goto 10
3069     if(xin(i) - xtol .gt. ac(2))  goto 10
3070     if(yin(i) + ytol .lt. ac(3))  goto 10
3071     if(yin(i) - ytol .gt. ac(4))  goto 10
3072     kp = kp + 1
3073     j = i
3074     xout(kp) = xin(i)
3075     yout(kp) = yin(i)
307610   continue
3077  enddo
3078  if (kp .lt. 2)  then
3079     if (kp .eq. 0)  then
3080        !--- both outside
3081        do  i = 1, 2
3082           x(i) = xin(i)
3083           y(i) = yin(i)
3084        enddo
3085     else
3086        x(1) = xin(j)
3087        y(1) = yin(j)
3088        x(2) = xin(3-j)
3089        y(2) = yin(3-j)
3090     endif
3091     !--- treat four cases = four sides of ac: low, up, left, right
3092     k = 0
3093     if (abs(y(2) - y(1)) .gt. ytol)  then
3094        t = (ac(3) - y(1)) / (y(2) - y(1))
3095        if (t .ge. 0. .and. t .lt. 1.)  then
3096           xc = x(1) + t * (x(2) - x(1))
3097           if (xc + xtol .ge. ac(1) .and. xc - xtol .le. ac(2))  then
3098              k = k + 1
3099              xr(k) = xc
3100              yr(k) = ac(3)
3101           endif
3102        endif
3103        t = (ac(4) - y(1)) / (y(2) - y(1))
3104        if (t .ge. 0. .and. t .lt. 1.)  then
3105           xc = x(1) + t * (x(2) - x(1))
3106           if (xc + xtol .ge. ac(1) .and. xc - xtol .le. ac(2))  then
3107              k = k + 1
3108              xr(k) = xc
3109              yr(k) = ac(4)
3110           endif
3111        endif
3112     endif
3113     if (abs(x(2) - x(1)) .gt. xtol)  then
3114        t = (ac(1) - x(1)) / (x(2) - x(1))
3115        if (t .ge. 0. .and. t .lt. 1.)  then
3116           yc = y(1) + t * (y(2) - y(1))
3117           if (yc + ytol .ge. ac(3) .and. yc - ytol .le. ac(4))  then
3118              k = k + 1
3119              yr(k) = yc
3120              xr(k) = ac(1)
3121           endif
3122        endif
3123        t = (ac(2) - x(1)) / (x(2) - x(1))
3124        if (t .ge. 0. .and. t .lt. 1.)  then
3125           yc = y(1) + t * (y(2) - y(1))
3126           if (yc + ytol .ge. ac(3) .and. yc - ytol .le. ac(4))  then
3127              k = k + 1
3128              yr(k) = yc
3129              xr(k) = ac(2)
3130           endif
3131        endif
3132     endif
3133     if (kp .eq. 0)  then
3134        if( k .eq. 2)  then
3135           do  i = 1, 2
3136              xout(i) = xr(i)
3137              yout(i) = yr(i)
3138           enddo
3139           kp = 2
3140        endif
3141     elseif (k .eq. 1)  then
3142        xout(2) = xr(1)
3143        yout(2) = yr(1)
3144        kp = 2
3145     elseif (k .gt. 1)  then
3146        if (abs(xr(1) - xout(1)) .lt. abs(xr(2) - xout(1)))  then
3147           xout(2) = xr(2)
3148           yout(2) = yr(2)
3149           kp = 2
3150        endif
3151     endif
3152  endif
3153end subroutine gxplxx
3154subroutine gxpm(n,x,y,ac)
3155  use gxx11_common
3156  implicit none
3157  integer i,iloop,k,n,nup
3158  real xerr,yerr
3159  !***********************************************************************
3160  !
3161  !   Purpose: plots a marker symbol if inside active window.
3162  !
3163  !--- Input:
3164  !   n          no. of marker symbols
3165  !   x          x positions
3166  !   y          y positions
3167  !   ac         active window
3168  !
3169  !   Author: H. Grote / CERN                        date: Dec. 9, 1988
3170  !                                           last mod: Dec. 9, 1988
3171  !
3172  !***********************************************************************
3173  real x(*),y(*),ac(4)
3174
3175  xerr=1.e-3*(ac(2)-ac(1))
3176  yerr=1.e-3*(ac(4)-ac(3))
3177  do  iloop=1,n,madim2
3178     nup=min(n,iloop+madim2-1)
3179     k=0
3180     do  i=iloop,nup
3181        if(x(i).lt.ac(1)-xerr)  goto 20
3182        if(x(i).gt.ac(2)+xerr)  goto 20
3183        if(y(i).lt.ac(3)-yerr)  goto 20
3184        if(y(i).gt.ac(4)+yerr)  goto 20
3185        k=k+1
3186        xp(k)=x(i)
3187        yp(k)=y(i)
318820      continue
3189     enddo
3190     if(k.gt.0) call gvpm(k,xp,yp)
3191  enddo
3192end subroutine gxpm
3193subroutine gxpmsw(n,x,y,ac)
3194  implicit none
3195  integer n
3196  !***********************************************************************
3197  !
3198  !   Purpose: plots a software (!) marker symbol if inside active window.
3199  !         this is necessary where the scaling of hardware symbols
3200  !         does not work (e.g. Apollo with GTS-GRAL).
3201  !         only symbols 1 to 5 (.+*ox) are supported.
3202  !
3203  !--- Input:
3204  !   n          no. of marker symbols
3205  !   x          x positions
3206  !   y          y positions
3207  !   ac         active window
3208  !
3209  !   Author: H. Grote / CERN                          date: May 11, 1989
3210  !                                               last mod: July 10, 1995
3211  !
3212  !***********************************************************************
3213  real x(*),y(*),ac(4)
3214  call gxpm(n,x,y,ac)
3215end subroutine gxpmsw
3216subroutine gxpnbl(string,ifirst,ilast)
3217  implicit none
3218  integer i,ifirst,ilast
3219  !***********************************************************************
3220  !
3221  !   Purpose: returns position of first and last non-blank in STRING
3222  !
3223  !--- Input
3224  !   string     character string
3225  !--- Output
3226  !   ifirst     first non-blank in string, or 0 if only blanks
3227  !   ilast      last non-blank
3228  !
3229  !   Author: H. Grote / CERN                        date: June 16, 1987
3230  !                                           last mod: June 16, 1987
3231  !
3232  !***********************************************************************
3233  character(*)  string
3234  ifirst=0
3235  ilast=0
3236  do i=1,len(string)
3237     if(string(i:i).ne.' ') then
3238        ifirst=i
3239        goto 20
3240     endif
3241  enddo
3242  goto 999
324320 continue
3244  do i=len(string),1,-1
3245     if(string(i:i).ne.' ') then
3246        ilast=i
3247        goto 999
3248     endif
3249  enddo
3250999 end subroutine gxpnbl
3251subroutine gxppow(alabl,ipower)
3252  implicit none
3253  integer i1,i2,ipower
3254  !***********************************************************************
3255  !
3256  !   Purpose: plots a power of ten as label
3257  !
3258  !--- Input
3259  !   alabl      text coordinates
3260  !   ipower     power to plot
3261  !
3262  !   Author: H. Grote / CERN                        date: June 16, 1987
3263  !                                           last mod: June 8, 1988
3264  !
3265  !***********************************************************************
3266  real alabl(4)
3267  character sdumm*10
3268  if(ipower.eq.0)  then
3269     call gxstx(alabl(1),alabl(3),' 1  ')
3270  elseif(ipower.eq.1)  then
3271     call gxstx(alabl(1),alabl(3),'10  ')
3272  else
3273     sdumm=' '
3274     write(sdumm,'(I10)')  ipower
3275     call gxpnbl(sdumm,i1,i2)
3276     call gxtx(alabl(1),alabl(3),'10<!>'//sdumm(i1:i2)//'<!>')
3277  endif
3278end subroutine gxppow
3279subroutine gxprwn(ixy,ncrv,icvref,nptval,ipcval,ipval,cval,val,nax,iaref,iapar,range,wn)
3280  use gxx11_common
3281  implicit none
3282  integer i,iadd,iauto,iaxr,ic,icurv,ifl,ip,ipc,iscalf,ixy,j,k,kset,&
3283       nax,ncrv,nextop,npint,npt,nref,nx
3284  real rmax,rmaxi,rmaxt,rmin,rmini,rmint,tolo
3285  !***********************************************************************
3286  !
3287  !   Purpose: calculates all window values for either x or y
3288  !
3289  !--- Input
3290  !   ixy        flag: 1 = x, 2 = y (only valid x points for y range)
3291  !   ncrv       number of curves (=ordered sets of (x,y) pairs) to plot
3292  !   icvref(i)  curve set for curve I
3293  !   nptval(i)  number of points ((x,y) pairs) in set I
3294  !   ipcval(i)  first x value of set I in array VAL (for range check)
3295  !   ipval(i)   first x or y value of set I in array VAL
3296  !   cval       array containing the x values for all sets (range check)
3297  !   val        array containing the x or y values for all sets
3298  !   nax        max. no. of x or y axes
3299  !   iaref(i)   axis reference number of set I. All x or y axes with
3300  !            this reference number will be scaled if automatic.
3301  !   iapar(j,K) axis parameters of x or y axis K
3302  !   range(j,K) lower and upper limit of axis K
3303  !--- Output
3304  !   wn(j,i)    lower and upper window values for set I
3305  !
3306  !   Author: H. Grote / CERN                        date: June 16, 1987
3307  !                                           last mod: Nov. 18, 1994
3308  !
3309  !***********************************************************************
3310
3311  integer nptval(*), ipcval(*), ipval(*), iaref(*), iapar(mpaxs,*), &
3312       icvref(*)
3313  real cval(*), val(*), range(2,*), wn(2,*)
3314  real rng(2)
3315  integer iref(mxaxs+myaxs)
3316  !
3317  !--- nref counts the number of axis reference numbers
3318  nref=0
3319  do icurv=1,ncrv
3320     kset=max(1,min(maxset,icvref(icurv)))
3321     iaxr=iaref(kset)
3322     !--- check whether there are axes with this ref. number
3323     do j=1,nref
3324        if(iaxr.eq.iref(j)) goto 80
3325     enddo
3326     !--- not yet in list
3327     nref=nref+1
3328     iref(nref)=iaxr
3329     !--- loop over related axes for scaling etc.
3330     !--- nextop gives the highest option for zero adjustment
3331     nextop=0
3332     !--- iscalf gives the highest scaling type request
3333     iscalf=0
3334     !--- iauto is 0 for automatic, 1 for hand scaling
3335     iauto=0
3336     do i=1,nax
3337        if(iapar(21,i).eq.iaxr) then
3338           nextop=max(nextop,iapar(22,i))
3339           iscalf=max(iscalf,iapar(1,i))
3340           iauto =max(iauto ,iapar(23,i))
3341        endif
3342     enddo
3343     if(iauto.ne.0)  then
3344        !--- hand scaling requested - get extrema of all ranges given
3345        ifl=0
3346        do i=1,nax
3347           if(iapar(21,i).eq.iaxr) then
3348              if(range(1,i).lt.range(2,i)) then
3349                 if(ifl.eq.0) then
3350                    ifl=1
3351                    rng(1)=range(1,i)
3352                    rng(2)=range(2,i)
3353                 endif
3354                 rng(1)=min(rng(1),range(1,i))
3355                 rng(2)=max(rng(2),range(2,i))
3356              endif
3357           endif
3358        enddo
3359        if(ifl.eq.0) then
3360           !--- no valid range found - use automatic scaling
3361           iauto=0
3362        endif
3363     endif
3364     if(iauto.eq.0) then
3365        !--- find minima and maxima of coordinates
3366        ifl=0
3367        do ic=icurv,ncrv
3368           k=max(1,min(maxset,icvref(ic)))
3369           if(iaxr.eq.iaref(k)) then
3370              !--- find min. and max. x or y values
3371              npt=nptval(ic)
3372              ip=ipval(ic)
3373              ipc = ipcval(ic)
3374              iadd = 0
3375              if (ixy .eq. 2)  then
3376                 !--- take only y values paired with valid x values
3377                 tolo = toleps * (axwndx(2,kset) - axwndx(1,kset))
3378                 do  j = 0, npt - 1
3379                    if (cval(ipc+j) .ge. axwndx(1, kset) - tolo           &
3380                         .and. cval(ipc+j) .le. axwndx(2, kset) + tolo)                    &
3381                         then
3382                       iadd = j
3383                       goto 32
3384                    endif
3385                 enddo
338632               continue
3387              endif
3388              if(ifl.eq.0) then
3389                 rmini=val(ip+iadd)
3390                 rmaxi=rmini
3391                 ifl=1
3392              endif
3393              do j=iadd,npt-1
3394                 if (ixy .eq. 1)  then
3395                    rmini=min(rmini,val(ip+j))
3396                    rmaxi=max(rmaxi,val(ip+j))
3397                 elseif (cval(ipc+j) .ge. axwndx(1, kset)                &
3398                      .and. cval(ipc+j) .le. axwndx(2, kset))  then
3399                    rmini=min(rmini,val(ip+j))
3400                    rmaxi=max(rmaxi,val(ip+j))
3401                 endif
3402              enddo
3403           endif
3404        enddo
3405     endif
3406     !   nx counts the axes belonging to IAXR
3407     nx=0
3408     do i=1,nax
3409        !--- keep interval number as given by user
3410        iapar(19,i)=iapar(2,i)
3411        if(iapar(21,i).eq.iaxr) then
3412           nx=nx+1
3413           if(iauto.eq.0) then
3414              !--- automatic scaling of this axis requested
3415              call gxarng(nextop,rmini,rmaxi,rmin,rmax,npint)
3416              if(iapar(2,i).lt.0)  iapar(19,i)=npint
3417           else
3418              !--- hand scaling
3419              rmin=rng(1)
3420              rmax=rng(2)
3421              if(nextop.eq.1) then
3422                 !--- start or end axis at 0. if possible
3423                 if(rmin.gt.0.) then
3424                    rmin=0.
3425                 elseif(rmax.lt.0.) then
3426                    rmax=0.
3427                 endif
3428              elseif(nextop.eq.2) then
3429                 !--- make axis symmetric around 0.
3430                 rmax=max(abs(rmin),abs(rmax))
3431                 rmin=-rmax
3432              endif
3433           endif
3434           !--- keep overall min. and max.
3435           if(nx.eq.1) then
3436              rmint=rmin
3437              rmaxt=rmax
3438           else
3439              rmint=min(rmint,rmin)
3440              rmaxt=max(rmaxt,rmax)
3441           endif
3442        endif
3443     enddo
3444     if(nx.eq.0) then
3445        !--- no axis found for this ref. number - automatic scale
3446        call gxarng(0,rmini,rmaxi,rmint,rmaxt,npint)
3447     endif
3448     !--- set windows
3449     do ic=icurv,ncrv
3450        k=max(1,min(maxset,icvref(ic)))
3451        if(iaref(k).eq.iaxr) then
3452           wn(1,k)=rmint
3453           wn(2,k)=rmaxt
3454        endif
3455     enddo
345680   continue
3457  enddo
3458999 end subroutine gxprwn
3459subroutine gxqaxs(type,naxis,npar,ipar,range,stext,sform)
3460  use gxx11_common
3461  implicit none
3462  integer i,naxis,npar
3463  !***********************************************************************
3464  !
3465  !   Purpose: returns axis parameters
3466  !
3467  !--- Input
3468  !   type     'X' for an x-axis, 'Y' for a y-axis
3469  !   naxis    axis number
3470  !--- Output
3471  !   npar     no. of axis parameters in IPAR
3472  !          or = 0 if NAXIS and/or TYPE are wrong, in which case the other
3473  !          Output parameters will not be set
3474  !   ipar     parameter list
3475  !   range(1) lower axis limit
3476  !      (2) upper axis limit
3477  !   stext    axis text
3478  !   sform    axis label format, e.g. '(F6.2)'
3479  !
3480  !   Author: H. Grote / CERN                        date: June 16, 1987
3481  !                                           last mod: June 16, 1987
3482  !
3483  !***********************************************************************
3484
3485  character(*)  type,stext,sform
3486  integer ipar(*)
3487  real range(2)
3488  npar=0
3489  if(type.eq.'X')  then
3490     if(naxis.gt.0.and.naxis.le.mxaxs) then
3491        npar=mpaxs
3492        stext=sxtext(naxis)
3493        sform=sxform(naxis)
3494        do i=1,mpaxs
3495           ipar(i)=ixapar(i,naxis)
3496        enddo
3497        do i=1,2
3498           range(i)=rangex(i,naxis)
3499        enddo
3500     endif
3501  elseif(type.eq.'Y')  then
3502     if(naxis.gt.0.and.naxis.le.myaxs) then
3503        npar=mpaxs
3504        stext=sytext(naxis)
3505        sform=syform(naxis)
3506        do i=1,mpaxs
3507           ipar(i)=iyapar(i,naxis)
3508        enddo
3509        do i=1,2
3510           range(i)=rangey(i,naxis)
3511        enddo
3512     endif
3513  endif
3514end subroutine gxqaxs
3515subroutine gxqcrv(nset,npar,ipar,symb)
3516  use gxx11_common
3517  implicit none
3518  integer i,npar,nset
3519  !***********************************************************************
3520  !
3521  !   Purpose: inquire curve set parameters
3522  !
3523  !--- Input
3524  !   nset    curve set number
3525  !--- Output
3526  !   npar     number of curve set parameters returned in IPAR
3527  !   ipar     parameter list
3528  !   symb     plot symbol
3529  !
3530  !   Author: H. Grote / CERN                        date: June 16, 1987
3531  !                                           last mod: June 16, 1987
3532  !
3533  !***********************************************************************
3534
3535  character(1) symb
3536  integer ipar(*)
3537  npar=0
3538  if(nset.gt.0.and.nset.le.maxset)  then
3539     npar=mpcurv
3540     do i=1,mpcurv
3541        ipar(i)=icvpar(i,nset)
3542     enddo
3543     symb=splotc(nset:nset)
3544  endif
3545end subroutine gxqcrv
3546subroutine gxqrvp(xf)
3547  implicit none
3548  integer ict,ierr
3549  real xf
3550  !***********************************************************************
3551  !
3552  !   Purpose: inquire view port ratio (y to x extension)
3553  !
3554  !--- Output
3555  !   xf       expansion factor
3556  !
3557  !   Author: H. Grote / CERN                        date: March 2, 1988
3558  !                                           last mod: March 2, 1988
3559  !
3560  !***********************************************************************
3561  real w(4),v(4)
3562  xf=1.
3563  !--- get current norm. transf. number
3564  call jqcntn(ierr,ict)
3565  if(ierr.ne.0) goto 999
3566  !--- get current window and viewport
3567  call jqnt(ict,ierr,w,v)
3568  if(ierr.ne.0) goto 999
3569  if(v(2).gt.v(1).and.v(4).gt.v(3))  then
3570     xf=(v(4)-v(3))/(v(2)-v(1))
3571  endif
3572999 end subroutine gxqrvp
3573subroutine gxqvar(name,intv,realv,charv)
3574  use gxx11_common
3575  implicit none
3576  integer intv
3577  real realv
3578  !***********************************************************************
3579  !
3580  !   Purpose: returns values of certain variables in common GXCOMM
3581  !
3582  !--- Input:
3583  !   name     name of the variable (character):
3584  !   = itermt   terminal workstation type (default = MTERMT)
3585  !   = interm   terminal workstation number (default  = MTTERM if
3586  !            GXASKU called, 0 otherwise for batch)
3587  !            if = 0, no graphics display on terminal
3588  !   = inmeta   metafile workstation number  (default = MTMETA)
3589  !            if = 0, no metafile written
3590  !   = ierrun   GKS error file unit number (default = MERRUN)
3591  !   = imetun   metafile unit  (default = METAUN)
3592  !   = inunit   terminal or default READ unit (default = 5)
3593  !   = iounit   terminal or default PRINT unit (default = 6)
3594  !   = isfflg   =0 (default) for square, 1 for full screen area
3595  !   = isqflg   =0 (default) for independent window optimization in x and y,
3596  !             =1 for an identical window range in x and y.
3597  !         this means that if:
3598  !                            ISFFLG=0, ISQFLG=1
3599  !                            and the viewport has not been tampered with
3600  !                            and the x and y scales are identical
3601  !         then
3602  !            (on a plotter) a circle will be plotted as a circle (!)
3603  !                            if GXPLOT is called
3604  !   = iwtflg   if = 0 (default), no action.
3605  !         if = 1 (set by GXASKU if interactive), GXPLOT will wait for some
3606  !         Input from the keyboard (e.g. <CR>) before returning so that you
3607  !         can look at the picture. The waiting routine GXWAIT can be called
3608  !         separately.
3609  !   = iclflg   =0 : no action; = 1 (default): causes a "clear workstations"
3610  !         at the end of GXPLOT. This is simply done by
3611  !         if(INTERM.GT.0)  CALL GCLRWK(INTERM,0)
3612  !         if(INMETA.GT.0)  CALL GCLRWK(INMETA,0)
3613  !         in case you want to do it separately.
3614  !   = inormt   normalization transformation number (default=MNORMT)
3615  !   = ipseps   .ps (1), .eps (2), else no Output
3616  !   = idinit   treat first GXINIT call as dummy if not zero
3617  !   = nxpix    x size of window in pixels (X11)
3618  !   = nypix    y size of window in pixels (X11)
3619  !   = xmetaf   paper length in cm for metafile plotting
3620  !   = ymetaf   paper width in cm for metafile plotting
3621  !            if either XMETAF or YMETAF = 0. (default), then the
3622  !            default square will be plotted
3623  !   = serrnm   GKS error file name (default GXFERR)
3624  !   = smetnm   Metafile name (default GXMETA)
3625  !   = sdefnl   new line start default in axis titles
3626  !
3627  !--- Output:
3628  !   intv     integer value if the variable is INTEGER
3629  !   realv    real value if the variable is REAL
3630  !   charv    if the variable is CHARACTER
3631  !
3632  !   Author: H. Grote / CERN                        date: June 16, 1987
3633  !                                           last mod: May 12, 1993
3634  !
3635  !***********************************************************************
3636
3637  character(*) name,charv
3638  character(6) code
3639  code=name
3640  if    (code.eq.'ITERMT')  then
3641     intv=itermt
3642  elseif(code.eq.'INTERM')  then
3643     intv=interm
3644  elseif(code.eq.'INMETA')  then
3645     intv=inmeta
3646  elseif(code.eq.'IERRUN')  then
3647     intv=ierrun
3648  elseif(code.eq.'IMETUN')  then
3649     intv=imetun
3650  elseif(code.eq.'INUNIT')  then
3651     intv=inunit
3652  elseif(code.eq.'IOUNIT')  then
3653     intv=iounit
3654  elseif(code.eq.'ISFFLG')  then
3655     intv=isfflg
3656  elseif(code.eq.'ISQFLG')  then
3657     intv=isqflg
3658  elseif(code.eq.'IWTFLG')  then
3659     intv=iwtflg
3660  elseif(code.eq.'ICLFLG')  then
3661     intv=iclflg
3662  elseif(code.eq.'INORMT')  then
3663     intv=inormt
3664  elseif(code.eq.'IPSEPS')  then
3665     intv=ipseps
3666  elseif(code.eq.'IDINIT')  then
3667     intv=idinit
3668  elseif(code.eq.'NXPIX')  then
3669     intv = nxpix
3670  elseif(code.eq.'NYPIX')  then
3671     intv = nypix
3672  elseif(code.eq.'XMETAF')  then
3673     realv=xmetaf
3674  elseif(code.eq.'YMETAF')  then
3675     realv=ymetaf
3676  elseif(code.eq.'SERRNM')  then
3677     charv=serrnm
3678  elseif(code.eq.'SMETNM')  then
3679     charv=smetnm
3680  elseif(code.eq.'SDEFNL')  then
3681     charv=sdefnl
3682  endif
3683end subroutine gxqvar
3684subroutine gxqwac(wact)
3685  use gxx11_common
3686  implicit none
3687  integer i
3688  !***********************************************************************
3689  !
3690  !   Purpose: returns current active user area (inside frame) in NDC
3691  !
3692  !--- Output
3693  !   wact     active window in NDC
3694  !
3695  !   Author: H. Grote / CERN                        date: Dec 17, 1987
3696  !                                           last mod: Dec 17, 1987
3697  !
3698  !***********************************************************************
3699
3700  real wact(4)
3701  do i=1,4
3702     wact(i)=actwnd(i)
3703  enddo
3704end subroutine gxqwac
3705subroutine gxrdtx(lrunit,sline,ierr)
3706  implicit none
3707  integer ierr,lrunit
3708  !***********************************************************************
3709  !
3710  !   reads a character string from LRUNIT, recovers from
3711  !   empty carriage return under VM (string = blank).
3712  !
3713  !--- Input
3714  !   lrunit       Input unit
3715  !--- Output
3716  !   sline        string read, or blank if <CR>
3717  !   ierr         = 0 if no error, else = 1
3718  !
3719  !   Author hG  11.2.86
3720  !
3721  !***********************************************************************
3722  character sline*(*)
3723  ierr=0
3724  sline=' '
3725  read(lrunit,'(A)',err=30,end=30) sline
3726  goto 999
372730 ierr=1
3728999 end subroutine gxrdtx
3729subroutine gxrest(isave,rsave)
3730  implicit none
3731  !***********************************************************************
3732  !
3733  !   Purpose: restores GKS settings
3734  !
3735  !--- Input
3736  !   isave     integer list of saved values  (GXINIT def. in brackets)
3737  !       1   norm. transf. number  (1)
3738  !       2   line style             (1)
3739  !       3,4 hor. and vert. text alignment  (0,0)
3740  !       5,6 font and precision  (1,0)
3741  !         7 text colour index   (1)
3742  !         8 marker colour index (1)
3743  !         9 polyline colour index (1)
3744  !        10 marker type           (3)
3745  !        11 text path             (0)
3746  !        12 fill area interior style (0)
3747  !        13 fill area style index  (if interior style = 2)
3748  !   rsave     floating list of saved values
3749  !       1-4 window               (0.,1.,0.,1.)
3750  !       5-8 viewport             (0.,1.,0.,WFACT)
3751  !       9   character height   (0.01)
3752  !     10,11 character up vector  (0.,1.)
3753  !        12 line width scale factor  (1.)
3754  !        13 marker scale factor      (1.)
3755  !        14 character spacing factor (0.)
3756  !        15 character expansion factor (1.)
3757  !
3758  !   Author: H. Grote / CERN                        date: June 16, 1987
3759  !                                           last mod: March 7, 1988
3760  !
3761  !***********************************************************************
3762  integer isave(*)
3763  real    rsave(*)
3764  !
3765  if(isave(1).ne.0)  then
3766     !     call jselnt(isave(1))
3767     call jswn(isave(1),rsave(1),rsave(2),rsave(3),rsave(4))
3768  endif
3769  call jsln(isave(2))
3770  call jstxal(isave(3),isave(4))
3771  call jstxfp(isave(5),isave(6))
3772  call jstxci(isave(7))
3773  call jspmci(isave(8))
3774  call jsplci(isave(9))
3775  call jsmk(isave(10))
3776  !  call jstxp(isave(11))
3777  call jsfais(isave(12))
3778  !  call jsfasi(isave(13))
3779  !
3780  call jschh(rsave(9))
3781  call jschup(rsave(10),rsave(11))
3782  call jslwsc(rsave(12))
3783  call jsmksc(rsave(13))
3784  !  call jschsp(rsave(14))
3785  call jschxp(rsave(15))
3786999 end subroutine gxrest
3787subroutine gxsave(isave,rsave,ierr)
3788  implicit none
3789  integer ierr
3790  !***********************************************************************
3791  !
3792  !   Purpose: saves current GKS settings
3793  !
3794  !--- Output
3795  !   isave     integer list of saved values
3796  !       1   norm. transf. number
3797  !       2   line style
3798  !       3,4 hor. and vert. text alignment
3799  !       5,6 font and precision
3800  !         7 text colour index
3801  !         8 marker colour index
3802  !         9 polyline colour index
3803  !        10 marker type
3804  !        11 text path
3805  !        12 fill area interior style
3806  !        13 fill area style index  (if interior style = 2)
3807  !   rsave     floating list of saved values
3808  !       1-4 window               (0.,1.,0.,1.)
3809  !       5-8 viewport             (0.,1.,0.,WFACT)
3810  !       9   character height   (0.01)
3811  !     10,11 character up vector  (0.,1.)
3812  !        12 line width scale factor  (1.)
3813  !        13 marker scale factor      (1.)
3814  !        14 character spacing factor (0.)
3815  !        15 character expansion factor (1.)
3816  !   ierr      0 if OK, or GKS error number
3817  !
3818  !   Author: H. Grote / CERN                        date: June 16, 1987
3819  !                                           last mod: March 7, 1988
3820  !
3821  !***********************************************************************
3822  integer isave(*)
3823  real    rsave(*)
3824  !
3825  call jqcntn(ierr,isave(1))
3826  if(ierr.ne.0) goto 999
3827  call jqln(ierr,isave(2))
3828  if(ierr.ne.0) goto 999
3829  call jqtxal(ierr,isave(3),isave(4))
3830  if(ierr.ne.0) goto 999
3831  call jqtxfp(ierr,isave(5),isave(6))
3832  if(ierr.ne.0) goto 999
3833  call jqtxci(ierr,isave(7))
3834  if(ierr.ne.0) goto 999
3835  call jqpmci(ierr,isave(8))
3836  if(ierr.ne.0) goto 999
3837  call jqplci(ierr,isave(9))
3838  if(ierr.ne.0) goto 999
3839  call jqmk(ierr,isave(10))
3840  if(ierr.ne.0) goto 999
3841  !  call jqtxp(ierr,isave(11))
3842  if(ierr.ne.0) goto 999
3843  call jqfais(ierr,isave(12))
3844  if(ierr.ne.0) goto 999
3845  !  call jqfasi(ierr,isave(13))
3846  if(ierr.ne.0) goto 999
3847  !
3848  call jqnt(isave(1),ierr,rsave(1),rsave(5))
3849  if(ierr.ne.0) goto 999
3850  call jqchh(ierr,rsave(9))
3851  if(ierr.ne.0) goto 999
3852  call jqchup(ierr,rsave(10),rsave(11))
3853  if(ierr.ne.0) goto 999
3854  call jqlwsc(ierr,rsave(12))
3855  if(ierr.ne.0) goto 999
3856  call jqmksc(ierr,rsave(13))
3857  if(ierr.ne.0) goto 999
3858  !  call jqchsp(ierr,rsave(14))
3859  if(ierr.ne.0) goto 999
3860  call jqchxp(ierr,rsave(15))
3861  if(ierr.ne.0) goto 999
3862999 end subroutine gxsave
3863subroutine gxsaxs(type,naxis,npar,ipar,range,stext,sform)
3864  use gxx11_common
3865  implicit none
3866  integer i,naxis,npar
3867  !***********************************************************************
3868  !
3869  !   Purpose: set axis parameters
3870  !
3871  !--- Input
3872  !   type     'X' for an x-axis, 'Y' for a y-axis
3873  !   naxis    axis number
3874  !   npar     parameters 1 to NPAR will be taken from IPAR
3875  !   ipar     parameter list
3876  !   range(1) lower axis limit
3877  !      (2) upper axis limit
3878  !   stext    axis text - only plotted if first character not blank
3879  !   sform    axis label format, e.g. '(F6.2)'
3880  !
3881  !----------- REMARK.
3882  !          no action if TYPE and/or NAXIS are wrong.
3883  !
3884  !   Author: H. Grote / CERN                        date: June 16, 1987
3885  !                                           last mod: June 16, 1987
3886  !
3887  !***********************************************************************
3888
3889  character(*)  type,stext,sform
3890  integer ipar(*)
3891  real range(2)
3892  if(type.eq.'X')  then
3893     if(naxis.gt.0.and.naxis.le.mxaxs) then
3894        sxtext(naxis)=stext
3895        sxform(naxis)=sform
3896        do i=1,min(npar,mpaxs)
3897           ixapar(i,naxis)=ipar(i)
3898        enddo
3899        do i=1,2
3900           rangex(i,naxis)=range(i)
3901        enddo
3902     endif
3903  elseif(type.eq.'Y')  then
3904     if(naxis.gt.0.and.naxis.le.myaxs) then
3905        sytext(naxis)=stext
3906        syform(naxis)=sform
3907        do i=1,min(npar,mpaxs)
3908           iyapar(i,naxis)=ipar(i)
3909        enddo
3910        do i=1,2
3911           rangey(i,naxis)=range(i)
3912        enddo
3913     endif
3914  endif
3915end subroutine gxsaxs
3916subroutine gxscal(xmin,xmax,xlo,xhi,nint)
3917  implicit none
3918  integer i,icase,idistl,mrange,n1,n2,nint,niv
3919  real x1,x2,xhi,xlo,xmax,xmin
3920  !***********************************************************************
3921  !
3922  !   Purpose: for a given arbitrary interval, finds the nearest interval
3923  !         in round numbers and a good subdivision
3924  !
3925  !--- Input:
3926  !   xmin          lower corner of interval
3927  !   xmax          upper corner of interval
3928  !
3929  !--- Output:
3930  !   xlo           lower corner of (possibly) extended interval, round
3931  !   xhi           upper corner (dito)
3932  !   nint          proposed number of intervals (zero will be precisely
3933  !               on the limit of a subinterval if included in range)
3934  !
3935  !   Author: H. Grote / CERN                        date: Sept. 7, 1987
3936  !   last modification:                                   Jan. 12, 1988
3937  !
3938  !***********************************************************************
3939  parameter (mrange=10)
3940  integer iv(mrange+1)
3941  double precision rangl(mrange+1)
3942  double precision xhigh,xlow,ztol1,err1,dist,distl,distn,          &
3943       distr,sdist
3944  save iv, rangl, err1
3945  data iv/10,12,8,10,10,12,8,10,12,8,10/
3946  data rangl/1.d0,1.2d0,1.6d0,2.d0,2.5d0,3.d0,4.d0,5.d0,            &
3947       6.d0,8.d0,10.d0/
3948  data ztol1,err1/5.d-4,1.d-8/
3949  !
3950  !--- prepare Input data: consider only the case of at least one positive
3951  !   value. a boundary too near to zero will be set to zero.
3952  !
3953  x1=min(xmin,xmax)
3954  x2=max(xmin,xmax)
3955  if(x1.eq.x2)  then
3956     if(x1.lt.0.)  then
3957        x2=0.
3958     elseif(x1.gt.0.)  then
3959        x1=0.
3960     else
3961        x1=0.
3962        x2=1.
3963     endif
3964  endif
3965  if(x2.ge.0.)  then
3966     icase=1
3967     xlow=x1
3968     xhigh=x2
3969  else
3970     icase=2
3971     xlow=-x2
3972     xhigh=-x1
3973  endif
3974  if(abs(xlow).lt.xhigh)  then
3975     if(abs(xlow)/xhigh.lt.2.d0*ztol1)  xlow=0.d0
3976  else
3977     if(xhigh/abs(xlow).lt.2.d0*ztol1)  xhigh=0.d0
3978  endif
3979  if(icase.eq.1.and.xhigh.eq.0.d0)  then
3980     icase=2
3981     xhigh=-xlow
3982     xlow=0.d0
3983  endif
3984  !
3985  !--- choose a reasonable (round) distance
3986  !
3987  distl=log10(xhigh-xlow)
3988  idistl=distl
3989  if(distl.lt.0.d0)  idistl=idistl-1
3990  distr=10.d0**idistl
3991  distn=(xhigh-xlow)/distr
3992  do i=1,mrange
3993     if(distn.le.rangl(i)+err1) goto 20
3994  enddo
399520 continue
3996  dist=rangl(i)*distr
3997  if(xlow.eq.0.d0)  then
3998     !
3999     !--- first case: one of the boundary values is zero
4000     !
4001     nint=iv(i)
4002     if(icase.eq.1)  then
4003        xlo=0.
4004        xhi=dist
4005     else
4006        xlo=-dist
4007        xhi=0.
4008     endif
4009  elseif(xlow.lt.0.d0)  then
4010     !
4011     !--- second case: zero is included in interval and should therefore come
4012     !   to coincide with a subinterval boundary
4013     !
4014     niv=iv(i)
4015     sdist=dist/niv
4016     n1=abs(xlow)/sdist+1.d0-ztol1
4017     n2=xhigh/sdist+1.d0-ztol1
4018     nint=n1+n2
4019     xlo=-n1*sdist
4020     xhi=n2*sdist
4021  else
4022     !
4023     !--- both boundaries are below or above zero
4024     !
4025     niv=iv(i)
4026     sdist=dist/niv
4027     n1=xlow/sdist+ztol1
4028     n2=xhigh/sdist+1.d0-ztol1
4029     nint=n2-n1
4030     xlow=n1*sdist
4031     xhigh=n2*sdist
4032     if(icase.eq.1)  then
4033        xlo=xlow
4034        xhi=xhigh
4035     else
4036        xlo=-xhigh
4037        xhi=-xlow
4038     endif
4039  endif
4040end subroutine gxscal
4041subroutine gxschf(imode,iort,ch,chret,chwid)
4042  implicit none
4043  integer ierr,iffo,imode,iort,ippr
4044  real ch,chhxf,chret,chwid,hxf,xf
4045  !***********************************************************************
4046  !
4047  !   Purpose: set character height and orientation with correct scales
4048  !
4049  !--- Input
4050  !   imode    if 0, inquire only. If > 0, set height and exp. factor
4051  !   iort     text orientation: 1 horizontal, 2 vertical
4052  !   ch       character height for a standard viewport
4053  !--- Output
4054  !   chret    character height actually set
4055  !   chwid    character width
4056  !
4057  !   Author: H. Grote / CERN                          date: March 2, 1988
4058  !                                                last mod: May 16,  1995
4059  !
4060  !***********************************************************************
4061  !--- set height expansion factor if font
4062  call jqtxfp(ierr, iffo, ippr)
4063  if (imode .eq. 0 .and. iffo .lt. 0)  then
4064     chhxf = 1.5
4065  else
4066     chhxf = 1.
4067  endif
4068  call gxqrvp(hxf)
4069  if (iort .eq. 1)  then
4070     chret = ch * chhxf
4071     xf = hxf
4072     if(imode .gt. 0) call jschup(0., 1.)
4073  else
4074     chret = hxf * ch
4075     xf = 1. / hxf
4076     if(imode .gt. 0) call jschup(-1., 0.)
4077  endif
4078  chwid = .9 * chret * xf
4079  if (imode .gt. 0)  then
4080     call jschh(chret)
4081     call jschxp(xf)
4082  endif
4083999 end subroutine gxschf
4084subroutine gxscol(icol)
4085  use gxx11_common
4086  implicit none
4087  integer icol
4088  !***********************************************************************
4089  !
4090  !   Purpose: set foreground colour
4091  !
4092  !--- Input
4093  !   icol     requested colour
4094  !
4095  !   Author: H. Grote / CERN                        date: Apr. 7, 1995
4096  !                                           last mod: Apr. 7, 1995
4097  !
4098  !***********************************************************************
4099
4100  !      character chst * 16
4101  icucol = max(1, mod(icol - 1, mcolor) + 1)
4102end subroutine gxscol
4103subroutine gxscrv(nset,npar,ipar,symb)
4104  use gxx11_common
4105  implicit none
4106  integer i,npar,nset
4107  !***********************************************************************
4108  !
4109  !   Purpose: set curve set parameters
4110  !
4111  !--- Input
4112  !   nset     curve set number
4113  !   npar     parameters 1 to NPAR will be taken from IPAR
4114  !   ipar     parameter list
4115  !   symb     plot symbol
4116  !
4117  !   Author: H. Grote / CERN                        date: June 16, 1987
4118  !                                           last mod: June 16, 1987
4119  !
4120  !***********************************************************************
4121
4122  character(1) symb
4123  integer ipar(*)
4124  if(nset.gt.0.and.nset.le.maxset)  then
4125     do i=1,min(npar,mpcurv)
4126        icvpar(i,nset)=ipar(i)
4127     enddo
4128     splotc(nset:nset)=symb
4129  endif
4130end subroutine gxscrv
4131subroutine gxsdef(sitem,item)
4132  use gxx11_common
4133  implicit none
4134  integer i,i1,i2,item,j,k
4135  !***********************************************************************
4136  !
4137  !   Purpose: sets undefined variables or restores default values
4138  !
4139  !--- Input
4140  !   sitem    selects the set of values to be defined:
4141  !          'OPTION' for GKS options other than curves and axes: defaults
4142  !          'OPTINI' as for OPTION, but only undefined values are set
4143  !          'CURVE'  for curve set ITEM: set defaults
4144  !          'AXIS'   for both x and y axis no. ITEM: set defaults
4145  !          'XAXIS'  for x axis no. ITEM
4146  !          'YAXIS'  for y axis no. ITEM
4147  !          'DEVICE' for viewport: set defaults
4148  !   item     curve set or axis number. If = 0 , all curve sets or axes
4149  !   iflag    if = 0, define only undefined. if = 1, reset to defaults
4150  !
4151  !   Author: H. Grote / CERN                        date: June 16, 1987
4152  !                                           last mod: June 16, 1987
4153  !
4154  !***********************************************************************
4155
4156  character(*)  sitem
4157  character titem*50,sxtdef*60,sytdef*60,sxfdef*20,syfdef*20
4158  character spldef*(maxset)
4159  integer ixadef(mpaxs), iyadef(mpaxs), icvdef(mpcurv)
4160  real vp(4), vpdef(4), rxdef(2), rydef(2)
4161  real rgb(3,mcolor)
4162  character col(mcolor) * 16
4163  logical defaul,xaxis,yaxis
4164  save spldef, sxtdef, sxfdef, vp, ixadef, iyadef, icvdef,          &
4165       rxdef, rydef, rgb, col
4166  data rgb /3*0., 1.,0.,0., 0.,1.,0., 1.,0.,1., 0.,1.,1., 1.,1.,0./
4167  data col / 'black', 'red', 'green', 'blue', 'cyan',               &
4168       'magenta' /
4169  data spldef/'********************'/
4170  data sxtdef/' '/, sytdef/' '/
4171  data sxfdef/' '/, syfdef/' '/
4172  data vp / 0., 1., 0., 1. /
4173  data  vpdef/ 0.05, 0.95 ,0.05, 0.95 /
4174  data ixadef/0,-1,1,-99,-99,-99,10,10,2,2,1,9*0,                   &
4175       -99,0,0/
4176  data iyadef/0,-1,1,-99,-99,-99,10,10,2,2,1,9*0,                   &
4177       -99,0,0/
4178  data icvdef/1,1,1,1,0,1,0,0,0,10/
4179  data rxdef/0.,0./, rydef/0.,0./
4180
4181  call gxundf
4182  titem=sitem
4183  !------------------------------------------------
4184  !
4185  !    options
4186  !
4187  !------------------------------------------------
4188  if(titem(:6).eq.'OPTION'.or.titem(:6).eq.'OPTINI')  then
4189     defaul=titem(:6).eq.'OPTION'
4190     spsnam = ' '
4191     if(lnunit.ne.lundef.or.defaul) then
4192        lnunit=lundef
4193        inunit=miunit
4194     endif
4195     if(lounit.ne.lundef.or.defaul) then
4196        lounit=lundef
4197        iounit=mounit
4198     endif
4199     if(lnormt.ne.lundef.or.defaul) then
4200        lnormt=lundef
4201        inormt=mnormt
4202     endif
4203     if(lmetun.ne.lundef.or.defaul) then
4204        lmetun=lundef
4205        imetun=metaun
4206     endif
4207     if(lerrun.ne.lundef.or.defaul) then
4208        lerrun=lundef
4209        ierrun=merrun
4210     endif
4211     if(lmetax.ne.lundef.or.defaul) then
4212        lmetax=lundef
4213        xmetaf = mxsize
4214     endif
4215     if(lmetay.ne.lundef.or.defaul) then
4216        lmetay=lundef
4217        ymetaf = mysize
4218     endif
4219     if(ltermt.ne.lundef.or.defaul) then
4220        ltermt=lundef
4221        itermt=mtermt
4222     endif
4223     if(lnterm.ne.lundef.or.defaul) then
4224        lnterm=lundef
4225        interm=0
4226     endif
4227     if(lsfflg.ne.lundef.or.defaul) then
4228        lsfflg=lundef
4229        isfflg=0
4230     endif
4231     if(lsqflg.ne.lundef.or.defaul) then
4232        lsqflg=lundef
4233        isqflg=0
4234     endif
4235     if(lwtflg.ne.lundef.or.defaul) then
4236        lwtflg=lundef
4237        iwtflg=0
4238     endif
4239     if(lclflg.ne.lundef.or.defaul) then
4240        lclflg=lundef
4241        iclflg=1
4242     endif
4243     if(lnmeta.ne.lundef.or.defaul) then
4244        lnmeta=lundef
4245        inmeta=mtmeta
4246     endif
4247     if(lpseps.ne.lundef.or.defaul) then
4248        lpseps = lundef
4249        ipseps = 1
4250     endif
4251     if(ldinit.ne.lundef.or.defaul) then
4252        ldinit = lundef
4253        idinit = 0
4254     endif
4255     if(lxpix.ne.lundef.or.defaul) then
4256        lxpix = lundef
4257        nxpix = mxpix
4258     endif
4259     if(lypix.ne.lundef.or.defaul) then
4260        lypix = lundef
4261        nypix = mypix
4262     endif
4263     if(lerrnm.ne.lundef.or.defaul) then
4264        lerrnm=lundef
4265        serrnm='GXFERR'
4266     endif
4267     if(lmetnm.ne.lundef.or.defaul) then
4268        lmetnm=lundef
4269        smetnm='GXMETA'
4270     endif
4271     if(ldefnl.ne.lundef.or.defaul) then
4272        lmetnm=lundef
4273        sdefnl='//'
4274     endif
4275     if(lmpict.ne.lundef.or.defaul) then
4276        lmpict=lundef
4277     endif
4278     if(lttime.ne.lundef.or.defaul) then
4279        lttime=lundef
4280        !--- wait time for Higz in sec.
4281        wttime=0.5
4282     endif
4283     icucol = 1
4284     do  k = 1, mcolor
4285        do  i = 1, 3
4286           rgbcol(i,k) = rgb(i,k)
4287        enddo
4288        colour(k) = col(k)
4289     enddo
4290     !------------------------------------------------
4291     !
4292     !    device
4293     !
4294     !------------------------------------------------
4295  elseif(titem(:6).eq.'DEVICE') then
4296     !--- set normalization transformation
4297     !     call jselnt(inormt)
4298     do  i = 1, 4
4299        vptdef(i) = vpdef(i)
4300     enddo
4301     call gxsvpt(vp)
4302     !------------------------------------------------
4303     !
4304     !    curve sETS
4305     !
4306     !------------------------------------------------
4307  elseif(titem(:5).eq.'CURVE') then
4308     if(item.eq.0) then
4309        i1=1
4310        i2=maxset
4311     else
4312        i1=item
4313        i2=item
4314     endif
4315     do i=i1,i2
4316        do j=1,mpcurv
4317           icvpar(j,i)=icvdef(j)
4318        enddo
4319     enddo
4320     splotc(i1:i2)=spldef(i1:i2)
4321     !------------------------------------------------
4322     !
4323     !    axes
4324     !
4325     !------------------------------------------------
4326  else
4327     xaxis=titem(:3).eq.'XAX'.or.titem(:4).eq.'AXIS'
4328     yaxis=titem(:3).eq.'YAX'.or.titem(:4).eq.'AXIS'
4329     if(xaxis)  then
4330        if(item.eq.0) then
4331           i1=1
4332           i2=mxaxs
4333        else
4334           i1=item
4335           i2=item
4336        endif
4337        do i=i1,i2
4338           rangex(1,i)=rxdef(1)
4339           rangex(2,i)=rxdef(2)
4340           sxtext(i)=sxtdef
4341           sxform(i)=sxfdef
4342           do j=1,mpaxs
4343              if(ixadef(j).eq.-99) then
4344                 ixapar(j,i)=i
4345              else
4346                 ixapar(j,i)=ixadef(j)
4347              endif
4348           enddo
4349        enddo
4350     endif
4351     if(yaxis)  then
4352        if(item.eq.0) then
4353           i1=1
4354           i2=myaxs
4355        else
4356           i1=item
4357           i2=item
4358        endif
4359        do i=i1,i2
4360           rangey(1,i)=rydef(1)
4361           rangey(2,i)=rydef(2)
4362           sytext(i)=sytdef
4363           syform(i)=syfdef
4364           do j=1,mpaxs
4365              if(iyadef(j).eq.-99) then
4366                 iyapar(j,i)=i
4367              else
4368                 iyapar(j,i)=iyadef(j)
4369              endif
4370           enddo
4371        enddo
4372     endif
4373  endif
4374end subroutine gxsdef
4375subroutine gxsfop(fnparm,status,ierr)
4376  use gxx11_common
4377  implicit none
4378  integer ierr,ifirst,lgth
4379  !***********************************************************************
4380  !
4381  !   Purpose: opens the metafile or error file unit
4382  !
4383  !--- Input
4384  !   fnparm    selection parameter: starting 'MET' for metafile,
4385  !           'ERR' for error file, 'PSF' for Postscript, 'EPS' for
4386  !           encapsulated Postscript
4387  !   status    if ne ' ' then the unit will be opened with this,
4388  !           else 'UNKNOWN' will be used as default
4389  !--- Output
4390  !   ierr      =0 if everything OK
4391  !           =1 if FNPARM invalid
4392  !           =2 if the corresponding unit is not defined
4393  !
4394  !   Author: H. Grote / CERN                        date: Sept. 9, 1987
4395  !                                           last mod: May 12, 1993
4396  !
4397  !***********************************************************************
4398
4399  character(*) fnparm,status
4400  character smlocn * 80, sub*3, stat*7
4401  call gxundf
4402  sub=fnparm
4403  ierr=0
4404  !--- choose positive unit number (see higz)
4405  imetps = abs(imetun)
4406  if(status(:1).eq.' ')  then
4407     stat='UNKNOWN'
4408  else
4409     stat=status
4410  endif
4411  if(sub.eq.'MET')  then
4412     if(lmetun.eq.lundef) then
4413        if(lmetnm.eq.lundef) then
4414           lgth=len(smetnm)
4415           open(unit=imetps,file=smetnm(:lgth),status=stat)
4416        else
4417           open(unit=imetps,status=stat)
4418        endif
4419        lmetop=lundef
4420     else
4421        ierr=2
4422     endif
4423  elseif(sub .eq. 'EPS')  then
4424     if(lmetun .eq. lundef) then
4425        if(lmetnm .eq. lundef) then
4426           iepscf = iepscf + 1
4427           smlocn = smetnm
4428           call gxpnbl(smlocn, ifirst, lgth)
4429           write(smlocn(lgth+1:lgth+2), '(I2.2)')  iepscf
4430           spsnam = smlocn(:lgth+2) // '.eps'
4431           open(unit = imetps, file = spsnam, status = stat)
4432        else
4433           open(unit = imetps, status = stat)
4434        endif
4435        iepsop = 2
4436        lmetop = lundef
4437     else
4438        ierr=2
4439     endif
4440  elseif (sub .eq. 'PSF')  then
4441     if(lmetun.eq.lundef) then
4442        if(lmetnm .eq. lundef) then
4443           call gxpnbl(smetnm, ifirst, lgth)
4444           spsnam = smetnm(:lgth) // '.ps'
4445           open(unit = imetps, file = spsnam, status = stat)
4446        else
4447           open(unit = imetps, status = stat)
4448        endif
4449        iepsop = 1
4450        lmetop = lundef
4451     else
4452        ierr=2
4453     endif
4454  elseif(sub.eq.'ERR')  then
4455     if(lerrun.eq.lundef) then
4456        if(lerrnm.eq.lundef) then
4457           lgth=len(serrnm)
4458           open(unit=ierrun,file=serrnm(:lgth),status=stat)
4459        else
4460           open(unit=ierrun,status=stat)
4461        endif
4462        lerrop=lundef
4463     else
4464        ierr=2
4465     endif
4466  else
4467     ierr=1
4468  endif
4469end subroutine gxsfop
4470subroutine gxspmt
4471  implicit none
4472  !***********************************************************************
4473  !
4474  !   Purpose: sets defaults for line style, marker, text, and colour
4475  !
4476  !   Author: H. Grote / CERN                        date: June 16, 1987
4477  !                                           last mod: June 16, 1987
4478  !
4479  !***********************************************************************
4480  call jschup(0.,1.)
4481  call jsln(1)
4482  call jstxal(0,0)
4483  call jstxfp(1,2)
4484  call jstxci(1)
4485  call jspmci(1)
4486  call jsplci(1)
4487  call jsmksc(.5)
4488end subroutine gxspmt
4489subroutine gxsvar(name,intv,realv,charv)
4490  use gxx11_common
4491  implicit none
4492  integer intv
4493  real realv
4494  !***********************************************************************
4495  !
4496  !   Purpose: sets selected variables for plotting (in common GXCOMM)
4497  !
4498  !--- Input:
4499  !   name     name of the variable (character):
4500  !   = itermt   terminal workstation type (default = MTERMT)
4501  !   = interm   terminal workstation number (default  = MTTERM if
4502  !            GXASKU called, 0 otherwise for batch)
4503  !            if = 0, no graphics display on terminal
4504  !   = inmeta   metafile workstation number  (default = MTMETA)
4505  !            if = 0, no metafile written
4506  !   = iczebr   call (with any value) sets to LUNDEF (no more MZEBRA
4507  !             call)
4508  !   = wttime   Higz wait time in sec. before plotting into a window
4509  !   = ierrun   GKS error file unit number (default = MERRUN)
4510  !   = imetun   metafile unit  (default = METAUN)
4511  !   = inunit   terminal or default READ unit (default = 5)
4512  !   = iounit   terminal or default PRINT unit (default = 6)
4513  !   = isfflg   =0 (default) for square, 1 for full screen area
4514  !   = isqflg   =0 (default) for independent window optimization
4515  !             in x and y,
4516  !             =1 for an identical window range in x and y.
4517  !         this means that if:
4518  !                            ISFFLG=0, ISQFLG=1
4519  !                            and the viewport has not been tampered
4520  !                            with and the x and y scales are identical
4521  !         then
4522  !            (on a plotter) a circle will be plotted as a circle (!)
4523  !                            if GXPLOT is called
4524  !   = iwtflg   if = 0 (default), no action.
4525  !         if = 1 (set by GXASKU if interactive), GXPLOT will wait
4526  !         for some Input from the keyboard (e.g. <CR>) before
4527  !         returning so that you can look at the picture. The
4528  !         waiting routine GXWAIT can be called separately.
4529  !   = iclflg   =0 : no action; = 1 (default): causes a
4530  !         "clear workstations"
4531  !         at the end of GXPLOT. This is simply done by
4532  !         if(INTERM.GT.0)  CALL GCLRWK(INTERM,0)
4533  !         if(INMETA.GT.0)  CALL GCLRWK(INMETA,0)
4534  !         in case you want to do it separately.
4535  !   = inormt   normalization transformation number (default=MNORMT)
4536  !   = ipseps   .ps (1), .eps (2), else no Output
4537  !   = idinit   treat first GXINIT call as dummy if not zero
4538  !   = nxpix    x size of window in pixels (X11)
4539  !   = nypix    y size of window in pixels (X11)
4540  !   = xmetaf   paper length in cm for metafile plotting
4541  !   = ymetaf   paper width in cm for metafile plotting
4542  !            if either XMETAF or YMETAF = 0. (default), then the
4543  !            default square will be plotted
4544  !   = serrnm   GKS error file name (default GXFERR)
4545  !   = smetnm   Metafile name (default GXMETA)
4546  !   = sdefnl   new line start default in axis titles
4547  !
4548  !   intv     integer value if the variable is INTEGER
4549  !   realv    real value if the variable is REAL
4550  !   charv    if the variable is CHARACTER
4551  !
4552  !   Author: H. Grote / CERN                        date: June 16, 1987
4553  !                                           last mod: May 24, 1993
4554  !
4555  !***********************************************************************
4556
4557  character(*) name,charv
4558  character(6) code
4559  call gxundf
4560  code=name
4561  if    (code.eq.'ITERMT')  then
4562     itermt=intv
4563     ltermt=lundef
4564  elseif(code.eq.'INTERM')  then
4565     interm=intv
4566     lnterm=lundef
4567  elseif(code.eq.'INMETA')  then
4568     inmeta=intv
4569     lnmeta=lundef
4570  elseif(code.eq.'ICZEBR')  then
4571     iczebr=lundef
4572  elseif(code.eq.'WTTIME')  then
4573     wttime = realv
4574     lttime = lundef
4575  elseif(code.eq.'IERRUN')  then
4576     ierrun=intv
4577     lerrun=lundef
4578  elseif(code.eq.'IMETUN')  then
4579     imetun=intv
4580     lmetun=lundef
4581  elseif(code.eq.'INUNIT')  then
4582     inunit=intv
4583     lnunit=lundef
4584  elseif(code.eq.'ITSEOP')  then
4585     itseop=intv
4586     ltseop=lundef
4587  elseif(code.eq.'IOUNIT')  then
4588     iounit=intv
4589     lounit=lundef
4590  elseif(code.eq.'ISFFLG')  then
4591     isfflg=intv
4592     lsfflg=lundef
4593  elseif(code.eq.'ISQFLG')  then
4594     isqflg=intv
4595     lsqflg=lundef
4596  elseif(code.eq.'IWTFLG')  then
4597     iwtflg=intv
4598     lwtflg=lundef
4599  elseif(code.eq.'ICLFLG')  then
4600     iclflg=intv
4601     lclflg=lundef
4602  elseif(code.eq.'INORMT')  then
4603     inormt=intv
4604     lnormt=lundef
4605  elseif(code.eq.'IPSEPS')  then
4606     ipseps=intv
4607     lpseps=lundef
4608  elseif(code.eq.'IDINIT')  then
4609     idinit=intv
4610     ldinit=lundef
4611  elseif(code.eq.'NXPIX')  then
4612     nxpix = intv
4613     lxpix = lundef
4614  elseif(code.eq.'NYPIX')  then
4615     nypix = intv
4616     lypix = lundef
4617  elseif(code.eq.'XMETAF')  then
4618     xmetaf=realv
4619     lmetax=lundef
4620  elseif(code.eq.'YMETAF')  then
4621     ymetaf=realv
4622     lmetay=lundef
4623  elseif(code.eq.'SERRNM')  then
4624     serrnm=charv
4625     lerrnm=lundef
4626  elseif(code.eq.'SMETNM')  then
4627     smetnm=charv
4628     lmetnm=lundef
4629  elseif(code.eq.'SDEFNL')  then
4630     sdefnl=charv
4631     ldefnl=lundef
4632  endif
4633end subroutine gxsvar
4634subroutine gxstep
4635  use gxx11_common
4636  implicit none
4637  integer ierr
4638  !***********************************************************************
4639  !
4640  !   Purpose: opens .eps file
4641  !
4642  !   Author: H. Grote / CERN                        date: May 12, 1993
4643  !                                           last mod: May 12, 1993
4644  !
4645  !***********************************************************************
4646
4647  if (iepsop .eq. -1)  then
4648     call gxsfop('PSFILE','UNKNOWN',ierr)
4649  else
4650     call gxsfop('EPSFILE','UNKNOWN',ierr)
4651  endif
4652  call gxopps(imetun, ipstyp)
4653end subroutine gxstep
4654subroutine gxstx(xpch, ypch, ch)
4655  use gxx11_common
4656  implicit none
4657  integer i,ich,ie,ierr,ifont,ifttmp,ihort,inttmp,iprec,ipstmp,     &
4658       ivert,k,lch,np
4659  real chsize,chux,chuy,cosa,enorm,exfact,sina,wid,width,xcoord,    &
4660       xmult,xpch,xshift,ycoord,ymult,ypch,yshift
4661  !***********************************************************************
4662  !
4663  !   Purpose: writes a software character string for fonts 1, -13
4664  !
4665  !--- Input:
4666  !   xpch     x position
4667  !   ypch     y position
4668  !   ch       string
4669  !
4670  !   Author: H. Grote / CERN                        date: Dec. 14, 1990
4671  !                                           last mod: May 13, 1993
4672  !**********************************************************************
4673  character(*) ch
4674
4675  real xp1(200), yp1(200), xpl(200), ypl(200), rsave(20)
4676  integer isave(20), ipen(200)
4677  real yfact(5)
4678  data yfact / 1.185, 1.,0.5, 0., -0.315 /
4679  wid=0.
4680  do i=1,200
4681     xp1(i)=0.
4682     yp1(i)=0.
4683     xpl(i)=0.
4684     ypl(i)=0.
4685  enddo
4686  do i=1,20
4687     rsave(i)=0.
4688  enddo
4689  !--- keep (e)ps flag
4690  ipstmp = ipseps
4691  !--- open .eps file if requested
4692  if (iepsop .lt. 0) call gxstep
4693  call jqtxfp(ie, ifont, iprec)
4694  if (ie .ne. 0) goto 999
4695  !--- start mod 7.6.96
4696  !    always write .ps or .eps file with a font, sw-characters only
4697  !    on screen
4698  if (ifont .ne. 1 .and. ifont .ne. -13)  then
4699     call gvtx(xpch, ypch, ch)
4700     goto 999
4701  else
4702     !--- switch terminal off, write file
4703     inttmp = interm
4704     interm = 0
4705     if (ifont .eq. 1)  then
4706        ifttmp = -1
4707     else
4708        ifttmp = -12
4709     endif
4710     call jstxfp(ifttmp, 2)
4711     call gvtx(xpch, ypch, ch)
4712     call jstxfp(ifont, 2)
4713     interm = inttmp
4714     !--- switch output file off
4715     ipseps = 0
4716     !--- end mod 7.6.96
4717  endif
4718  call gxsave(isave, rsave, ierr)
4719  call jsln(1)
4720  lch = len(ch)
4721  ihort = isave(3)
4722  ivert = isave(4)
4723  if (ihort .eq. 0) ihort = 1
4724  if (ivert .eq. 0) ivert = 4
4725  chsize = rsave(9)
4726  exfact = rsave(15)
4727  chux = rsave(10)
4728  chuy = rsave(11)
4729  enorm = 1. / sqrt(chux**2 + chuy**2)
4730  sina = -chux * enorm
4731  cosa = chuy * enorm
4732  ymult = chsize / 0.22
4733  xmult = exfact * ymult
4734  width = 0.
4735  ierr = 0
4736  do ich = 1, lch
4737     call gxfchr(0, ch(ich:ich), ifont, wid, np, ipen, xp1, yp1, ie)
4738     ierr = ierr + ie
4739     width = width + wid
4740  enddo
4741  if (ierr .eq. 0)  then
4742     xshift = 0.5 * (1 - ihort) * width * xmult
4743     yshift = - chsize * yfact(ivert)
4744     do ich = 1, lch
4745        call gxfchr(1, ch(ich:ich), ifont, wid, np, ipen, xp1, yp1,     &
4746             ierr)
4747        k = 0
4748        do i = 1, np
4749           if (ipen(i) .eq. 0)  then
4750              !--- pen up
4751              if (k .gt. 1)  call gvpl(k, xpl, ypl)
4752              k = 1
4753           else
4754              k = k + 1
4755           endif
4756           xcoord = xmult * xp1(i) + xshift
4757           ycoord = ymult * yp1(i) + yshift
4758           xpl(k) = xpch + cosa * xcoord - sina * ycoord
4759           ypl(k) = ypch + cosa * ycoord + sina * xcoord
4760        enddo
4761        if (k .gt. 1)  call gvpl(k, xpl, ypl)
4762        xshift = xshift + wid * xmult
4763     enddo
4764  else
4765     call gvtx(xpch, ypch, ch)
4766  endif
4767  ipseps = ipstmp
4768  call gxrest(isave, rsave)
4769999 end subroutine gxstx
4770subroutine gxsvpt(vp)
4771  use gxx11_common
4772  implicit none
4773  integer i
4774  real fdx,fdy
4775  !***********************************************************************
4776  !
4777  !   Purpose: sets workstation viewport. This needs a separate routine
4778  !         because of the screen size ratio (see below).
4779  !
4780  !--- Input
4781  !   vp       xlow, xup, ylow, yup of viewport.
4782  !          the factor of the screen ratio WFACT is applied to the
4783  !          gSVP call directly. The biggest possible screen size
4784  !          (square or full) is therefore always obtained with
4785  !          vP = (0.,1.,0.,1.) .
4786  !          in addition, if a metafile viewport other than the default
4787  !          is specified, this overrides the screen values.
4788  !
4789  !   Author: H. Grote / CERN                        date: June 16, 1987
4790  !                                           last mod: Nov 5, 1987
4791  !
4792  !***********************************************************************
4793
4794  real vp(4)
4795  fdx = vptdef(2) - vptdef(1)
4796  fdy = vptdef(4) - vptdef(3)
4797  do  i = 1, 2
4798     vploc(i) = vptdef(1) + fdx * vp(i)
4799     vploc(i+2) = vptdef(3) + fdy * vp(i+2)
4800  enddo
4801  vpfacx = vploc(2) - vploc(1)
4802  vpfacy = vploc(4) - vploc(3)
4803  call jsvp(1, vploc(1), vploc(2), vploc(3), vploc(4))
4804end subroutine gxsvpt
4805subroutine gxswnd(window)
4806  use gxx11_common
4807  implicit none
4808  !***********************************************************************
4809  !
4810  !   Purpose: sets the window for INORMT
4811  !
4812  !--- Input
4813  !   window    vector of length four (xlow, xup, ylow, yup)
4814  !   Author: H. Grote / CERN                        date: June 16, 1987
4815  !                                           last mod: June 16, 1987
4816  !
4817  !***********************************************************************
4818
4819  real window(4)
4820  call jswn(inormt,window(1),window(2),window(3),window(4))
4821end subroutine gxswnd
4822subroutine gxterm
4823  use gxx11_common
4824  implicit none
4825  !***********************************************************************
4826  !
4827  !   Purpose: terminates GKS PLOT package
4828  !
4829  !   Author: H. Grote / CERN                        date: June 16, 1987
4830  !                                           last mod: May 13, 1993
4831  !
4832  !***********************************************************************
4833
4834  call gxundf
4835  if(ltotin.eq.lundef)  then
4836     if(interm.gt.0.and.lacttm.eq.lundef)  then
4837        call wdawk(interm)
4838        call wclwk(interm)
4839     endif
4840     if(inmeta.gt.0)  then
4841        if (iepsop .gt. 0)  then
4842           call gxopps(0, 0)
4843        endif
4844     endif
4845     call wclks
4846     if (iepsop .eq. 1 .or. iepsop .eq. 2)  then
4847        close(imetps)
4848        iepsop = - iepsop
4849     endif
4850     lmetop = 0
4851  endif
4852end subroutine gxterm
4853subroutine gxtint
4854  use gxx11_common
4855  implicit none
4856  !***********************************************************************
4857  !
4858  !   set defaults for a few variables - first routine to call
4859  !
4860  !***********************************************************************
4861
4862  integer i, j
4863  do i = 1, maxset
4864     do j = 1, 2
4865        axwndx(j,i) = 0
4866        axwndy(j,i) = 0
4867     enddo
4868     do j = 1, 4
4869        cvwnwd(j,i) = 0
4870     enddo
4871  enddo
4872  do i = 1, mxaxs
4873     do j = 1, 2
4874        rangex(j,i) = 0
4875        rangey(j,i) = 0
4876     enddo
4877  enddo
4878  smetnm = ' '
4879  serrnm = ' '
4880  do i = 1, mxaxs
4881     sxtext(i) = ' '
4882     sxform(i) = ' '
4883  enddo
4884  do i = 1, myaxs
4885     sytext(i) = ' '
4886     syform(i) = ' '
4887  enddo
4888  splotc = ' '
4889  stortx = ' '
4890  sdefnl = ' '
4891end subroutine gxtint
4892subroutine gxtx(xt,yt,text)
4893  implicit none
4894  integer i,ierr,ifdef,ifloc,ifont,igts,ihor,ihoru,in,ip,ipass,ipk, &
4895       iprec,ivert,ivertu,k,kfpos,l,last,ln,lnk,mchar,mfont,ms
4896  real ax,axup,ay,ayup,cang,chf,chh,chux,chuy,chxp,crf,ctf,cwf,cxl, &
4897       cyl,f,falign,sang,sq,t,x,xlift,xt,y,ylift,yt
4898  !***********************************************************************
4899  !
4900  !   Purpose: plots mixture of Roman and Greek text, superscripts
4901  !         and subscripts. Arguments exactly as GTX.
4902  !
4903  !--- Input:
4904  !   xt       text x position (as for GTX)
4905  !   yt       text y position (as for GTX)
4906  !   text     text (as for GTX)
4907  !          strings included in <G>...<G> appear as Greek,
4908  !          strings included in <!>...<!> appear as superscripts,
4909  !          strings included in <?>...<?> as subscripts.
4910  !          example:  TEXT='<G>a<!>b<!><G>'
4911  !          gives "alpha to the power of beta"
4912  !
4913  !   Author: H. Grote / CERN                        date: June 7, 1988
4914  !                                           last mod: May 13, 1993
4915  !
4916  !***********************************************************************
4917  parameter (ms=3,mchar=95,mfont=2)
4918  character text*(*),search(ms)*3,schar*(mchar),stemp*1
4919  integer ls(ms),is(ms)
4920  logical toggle(ms)
4921  real chgtsw(mchar,mfont)
4922  save crf, is, ls, chf, schar
4923  !--- set roman as default font
4924  !   data ifdEF/1/
4925  data crf/.5/
4926  data is/0,0,-13/
4927  data ls/3,3,3/
4928  data search/'<!>','<?>','<G>'/
4929  data chf/1.5/
4930  !--- list all possible keybord characters
4931  data schar/                                                       &
4932       ' 1234567890ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz!@#$%~&*()_+-={}[]:"|;''$><,.?,./'/
4933  !--- character widths for Roman and Greek fonts.
4934  data chgtsw/.7273,.9091,.9091,.9091,.9091,.9091,.9091,.9091,.9091,&
4935       .9091,.9091,.8182,.9545,.9545,.9545,.8636,.8182,.9545,1.,.3636,   &
4936       .7273,.9545,.7727,1.0909,1.,1.,.9545,1.,.9545,.9091,              &
4937       .7273,1.,.8182,1.0909,.9091,.8182,.9091,.8636,.8636,.8182,        &
4938       .8636,.8182,.5455,.8636,.8636,.3636,.4545,.7727,.3636,1.3636,     &
4939       .8636,.8636,.8636,.8636,.5909,.7727,.5455,.8636,.7273,1.,         &
4940       .7727,.7273,.7727,.4545,1.2273,.9545,.9091,1.0909,1.,1.1818,      &
4941       .7273,.6364,.6364,1.1818,1.1818,1.1818,1.1818,.6364,.6364,.6364,  &
4942       .6364,.4545,.7273,.3636,.4545,.4545,1.,1.0909,1.0909,.4545,       &
4943       .4545,.8182,.4545,.4545,1.,                                       &
4944       .7273,.9091,.9091,.9091,.9091,.9091,.9091,.9091,.9091,.9091,      &
4945       .9091,.8182,.9545,.9091,.8182,.8636,.9091,.7727,1.,.3636,         &
4946       .6818,.9545,.8182,1.0909,1.,.9091,1.,.6818,.9545,.8182,           &
4947       .7273,1.,.8182,1.,.8182,1.,.9091,.9545,.8636,.8182,               &
4948       .8182,.7273,1.,.8636,.9091,.5000,.6818,.8182,.7273,.9545,         &
4949       .8182,1.0455,1.,.6818,.8182,.9091,.9091,.7727,.9091,1.0455,       &
4950       .7273,.9545,.6818,.4545,1.2273,.9545,.9091,1.0909,1.,1.1364,      &
4951       .7273,.6364,.6364,1.1364,1.1364,1.1364,1.1364,.6364,.6364,.6364,  &
4952       .6364,.4545,.7273,.3636,.4545,.4545,1.,1.0909,1.0909,.4545,       &
4953       .4545,.8182,.4545,.4545,1./
4954  stemp = '\\'
4955  schar(87:87) = stemp
4956  lnk=999
4957  ipk=0
4958  last=len(text)
4959  if(last.eq.0)  goto 999
4960  do i=1,ms
4961     in=index(text,search(i)(:ls(i)))
4962     if(in.ne.0.and.in.lt.lnk) then
4963        lnk=in
4964        ipk=i
4965     endif
4966  enddo
4967  !--- call normal text routine if no special characters
4968  if(ipk.eq.0)  then
4969     call gxstx(xt,yt,text)
4970     goto 999
4971  endif
4972  !--- start processing
4973  call jqtxfp(ierr,ifont,iprec)
4974  if(ierr.ne.0) goto 999
4975  ifdef=ifont
4976  call jqtxal(ierr,ihoru,ivertu)
4977  if(ierr.ne.0) goto 999
4978  call jqchh(ierr,chh)
4979  if(ierr.ne.0) goto 999
4980  call jqchxp(ierr,chxp)
4981  if(ierr.ne.0) goto 999
4982  call jqchup(ierr,chux,chuy)
4983  if(ierr.ne.0) goto 999
4984  sq=sqrt(chux**2+chuy**2)
4985  sang=-chux/sq
4986  cang=chuy/sq
4987  if(ihoru.eq.0) then
4988     ihor=1
4989  else
4990     ihor=ihoru
4991  endif
4992  if(ivertu.eq.0) then
4993     ivert=5
4994  else
4995     ivert=ivertu
4996  endif
4997  call jstxal(1,5)
4998  !--- total character spacing in y direction
4999  cyl=chf*chh
5000  !--- alignment factor from vertical alignment definition
5001  falign=.5*(ivert-5)
5002  !--- x and y displacement in case of superscript
5003  axup=-.5*cyl*sang
5004  ayup=.5*cyl*cang
5005  !--- set initial starting point
5006  x=xt
5007  y=yt
5008  do ipass=1,2
5009     !--- reset to defaults
5010     ip=ipk
5011     ln=lnk
5012     k=0
5013     do i=1,ms
5014        toggle(i)=.false.
5015     enddo
5016     xlift=0.
5017     ylift=0.
5018     ctf=1.
5019     kfpos=1
5020     !
5021     !--- loop over text
5022     !
502330   if(k.ge.last) goto 70
5024     if(ip.eq.0)  then
5025        l=last
5026     else
5027        l=ln-1
5028     endif
5029     do i=1,l-k
5030        stemp=text(k+i:k+i)
5031        igts=index(schar,stemp)
5032        if(igts.eq.0) then
5033           cwf=1.
5034        else
5035           cwf=chgtsw(igts,kfpos)
5036        endif
5037        cxl=cwf*chxp*chh
5038        t=ctf*cxl
5039        ax=falign*axup
5040        ay=falign*ayup
5041        if(ipass.eq.2) then
5042           call gxstx(x+xlift,y+ylift,stemp)
5043        endif
5044        x=x+t*cang
5045        y=y+t*sang
5046     enddo
5047     k=l
5048     if(ip.ne.0)  then
5049        k=k+ls(ip)
5050        toggle(ip)=.not.toggle(ip)
5051        if(ip.eq.1)  then
5052           if(toggle(1)) then
5053              xlift=axup
5054              ylift=ayup
5055           else
5056              xlift=0.
5057              ylift=0.
5058           endif
5059        endif
5060        if(ip.le.2) then
5061           if(toggle(1).or.toggle(2))  then
5062              call jschh(crf*chh)
5063              ctf=crf
5064           else
5065              call jschh(chh)
5066              ctf=1.
5067           endif
5068        endif
5069        do i=3,ms
5070           if(i.eq.ip)  then
5071              if(toggle(i)) then
5072                 ifloc=is(i)
5073                 kfpos=i-1
5074                 if (i .eq. 3 .and. ifdef .ne. 1) ifloc = -12
5075              else
5076                 ifloc=ifdef
5077                 kfpos=1
5078              endif
5079              call jstxfp(ifloc,2)
5080           endif
5081        enddo
5082     endif
5083     ip=0
5084     ln=999
5085     if(k.lt.last)  then
5086        do i=1,ms
5087           in=index(text(k+1:last),search(i)(:ls(i)))
5088           if(in.ne.0.and.in.lt.ln)  then
5089              ln=in
5090              ip=i
5091           endif
5092        enddo
5093     endif
5094     if(ip.ne.0)  ln=ln+k
5095     goto 30
509670   continue
5097     f=.5*(ihor-1)
5098     x=xt+f*(xt-x)+ax
5099     y=yt+f*(yt-y)+ay
5100  enddo
510190 continue
5102  !--- restore defaults
5103  call jstxal(ihoru,ivertu)
5104  call jstxfp(ifont,iprec)
5105  call jschh(chh)
5106999 end subroutine gxtx
5107subroutine gxtx1(x,y,s,ac)
5108  implicit none
5109  real x,y
5110  !***********************************************************************
5111  !
5112  !   Purpose: plots a text if reference point inside active window.
5113  !
5114  !--- Input:
5115  !   x          x position
5116  !   y          y position
5117  !   s          text
5118  !   ac         active window
5119  !
5120  !   Author: H. Grote / CERN                        date: Dec. 9, 1988
5121  !                                           last mod: Dec. 9, 1988
5122  !
5123  !***********************************************************************
5124  real ac(4)
5125  character(*)  s
5126  if(x.ge.ac(1).and.x.le.ac(2).and.y.ge.ac(3).and.y.le.ac(4))       &
5127       call gxstx(x,y,s)
5128end subroutine gxtx1
5129subroutine gxundf
5130  use gxx11_common
5131  implicit none
5132  integer ifirst
5133  !***********************************************************************
5134  !
5135  !   Purpose: sets an integer for testing undefined variables
5136  !
5137  !   Author: H. Grote / CERN                        date: April 7, 1988
5138  !                                           last mod: April 7, 1988
5139  !
5140  !***********************************************************************
5141
5142  save ifirst
5143  data ifirst/0/
5144  if(ifirst.eq.0)  then
5145     ifirst=1
5146     if(lundef.eq.654321)  then
5147        lundef=654320
5148     else
5149        lundef=654321
5150     endif
5151  endif
5152end subroutine gxundf
5153subroutine gxwait
5154  use gxx11_common
5155  implicit none
5156  !***********************************************************************
5157  !
5158  !   Purpose: waits for Input from keyboard  (e.g. <CR>) if interactive
5159  !   allows emergency stop when entering STOP
5160  !
5161  !   Author: H. Grote / CERN                        date: June 16, 1987
5162  !                                           last mod: Feb. 26, 1988
5163  !
5164  !***********************************************************************
5165
5166  call gxundf
5167end subroutine gxwait
5168subroutine gxwclr(iun, ityp)
5169  use gxx11_common
5170  implicit none
5171  integer ityp,iun
5172  !***********************************************************************
5173  !
5174  !   Purpose: write .ps page end (clear)
5175  !
5176  !--- Input
5177  !   iun       not used
5178  !   ityp      not used
5179  !
5180  !   Author: H. Grote / CERN                          date: Apr. 27, 1995
5181  !                                                last mod: Apr. 27, 1995
5182  !
5183  !***********************************************************************
5184
5185  write(iutlps, '(a)')  'gs showpage gr'
5186  ! flush in a portable way
5187  endfile(iutlps)
5188  backspace(iutlps)
5189  ipage = ipage + 1
5190  stortx = '%%Page: number'
5191  write(stortx(15:20), '(i6)')  ipage
5192  istotx = 20
5193end subroutine gxwclr
5194subroutine gxwpep(iun, ityp)
5195  use gxx11_common
5196  implicit none
5197  integer i,iday,ihour,iii,imonth,isec,ittp,ityp,iun,iyear,l,minute
5198  real fsc
5199  !***********************************************************************
5200  !
5201  !   Purpose: write .ps or .eps file prologue or epilogue
5202  !
5203  !--- Input
5204  !   iun       Output unit number, if = 0: epilogue, > 0: prologue
5205  !   ityp      type of Output: 113 = eps,
5206  !           else ps with 114 = portrait, 115 = landscape
5207  !
5208  !   Author: H. Grote / CERN                        date: Apr. 27, 1995
5209  !                                           last mod: Apr. 27, 1995
5210  !
5211  !***********************************************************************
5212
5213  character(mlpro) pspro(mpspro), eppro(meppro), psdict(mdict),  &
5214       psepi(mpsep), epepi(mepep)
5215  character orient(2) * 12, head(mhead) * 60
5216  save ittp, orient, head, eppro, pspro, epepi, psepi, psdict
5217  data head / '$GX11psBegin',                                       &
5218       '0 setlinecap 0 setlinejoin', '<scale> ', ' ' /
5219  data orient / 'Portrait', 'Landscape' /
5220  data pspro / '%!PS-Adobe-2.0', '%%Title: ',                       &
5221       '%%Creator: gx11 version nnnn',                                   &
5222       '%%CreationDate: dd/mm/yy hh:mm',                                 &
5223       '%%Orientation: Landscape', '%%BoundingBox: nnn nnn nnn nnn',     &
5224       '%%Pages: (atend)', '%%EndComments' /
5225  data psepi / '%%Trailer', 'end', '%%EOF' /
5226  data eppro /'%!PS-Adobe-2.0 EPSF-2.0', '%%Title: filename',       &
5227       '%%Creator: gx11 version nnnn',                                   &
5228       '%%CreationDate: dd/mm/yy hh:mm',                                 &
5229       '%%Orientation: Landscape', '%%BoundingBox: nnn nnn nnn nnn',     &
5230       '%%Pages: 0', '%%EndComments' /
5231  data epepi / '$GX11psEnd showpage', '%%EOF' /
5232  data psdict / '/$GX11psDict 200 dict def', '$GX11psDict begin',   &
5233       '$GX11psDict /mtrx matrix put /l {lineto} bind def',              &
5234       '/m {moveto} bind def /s {stroke} bind def',                      &
5235       '/n {newpath} bind def /gs {gsave} bind def',                     &
5236       '/gr {grestore} bind def /clp {closepath} bind def',              &
5237       '/t {translate} bind def /sd {setdash} bind def',                 &
5238       '/fft {findfont} bind def /col-1 {} def /r {rotate} bind def',    &
5239       '/sf {scalefont setfont} bind def /sw {stringwidth} bind def',    &
5240       '/stwn { /fs exch def /fn exch def /text exch def fn findfont ',  &
5241       'fs sf text sw pop xs add /xs exch def} bind def',                &
5242       '/black {0 0 0 setrgbcolor} bind def',                            &
5243       '/blue {0 0 1 setrgbcolor} bind def',                             &
5244       '/green {0 1 0 setrgbcolor} bind def',                            &
5245       '/cyan {0 1 1 setrgbcolor} bind def',                             &
5246       '/red {1 0 0 setrgbcolor} bind def',                              &
5247       '/magenta {1 0 1 setrgbcolor} bind def',                          &
5248       '/yellow {1 1 0 setrgbcolor} bind def',                           &
5249       '/white {1 1 1 setrgbcolor} bind def',                            &
5250       '        end',                                                    &
5251       '/$GX11psBegin',                                                  &
5252       '     {$GX11psDict begin /$GX11psEnteredState save def} def',     &
5253       '/$GX11psEnd {$GX11psEnteredState restore end} def',              &
5254       '%%EndProlog' /
5255
5256  if (iun .gt. 0)  then
5257     !--- prologue
5258     fsc = 1. / msfact
5259     do  i = 1, mhead
5260        pshead(i) = head(i)
5261     enddo
5262     !        call datime(idate, itime)
5263     !        call datesp(idate, iyear, imonth, iday)
5264     !        call timesp(itime, ihour, minute)
5265     call mydtime(iyear, imonth, iday, ihour, minute, isec)
5266     if (ityp .eq. 113)  then
5267        !--- eps
5268        eppro(2)(10:) = spsnam
5269        write(eppro(3)(25:29), '(f5.2)')  versio
5270        write(eppro(4)(17:24), '(i2.2,''/'',i2.2,''/'',i2.2)')        &
5271             iyear, imonth, iday
5272        write(eppro(4)(26:33), '(i2.2,'':'',i2.2)')                   &
5273             ihour, minute
5274        eppro(5)(16:24) = orient(iorips)
5275        write(eppro(6)(15:30), '(4i4)')  ibbox
5276     else
5277        pspro(2)(10:) = spsnam
5278        write(pspro(3)(25:29), '(f5.2)')  versio
5279        write(pspro(4)(17:24), '(i2.2,''/'',i2.2,''/'',i2.2)')        &
5280             iyear, imonth, iday
5281        write(pspro(4)(26:33), '(i2.2,'':'',i2.2)')                   &
5282             ihour, minute
5283        pspro(5)(16:24) = orient(iorips)
5284        write(pspro(6)(15:30), '(4i4)')  ibbox
5285     endif
5286     iutlps = iun
5287     ittp = ityp
5288     !--- write prologue
5289     if (ittp .eq. 113)  then
5290        do  i = 1, meppro
5291           call gxpnbl(eppro(i), iii, l)
5292           write(iutlps, '(a)')  eppro(i)(:l)
5293        enddo
5294     else
5295        do  i = 1, mpspro
5296           call gxpnbl(pspro(i), iii, l)
5297           write(iutlps, '(a)')  pspro(i)(:l)
5298        enddo
5299     endif
5300     do  i = 1, mdict
5301        call gxpnbl(psdict(i), iii, l)
5302        write(iutlps, '(a)')  psdict(i)(:l)
5303     enddo
5304     write(pshead(3)(:20), '(2f7.3, '' scale'')')  fsc, fsc
5305     do  i = 1, mhead
5306        call gxpnbl(pshead(i), iii, l)
5307        write(iutlps, '(a)')  pshead(i)(:l)
5308     enddo
5309     if (ittp .ne. 113)  then
5310        ipage = ipage + 1
5311        write(iutlps, '(a,i5)') '%%Page: number', ipage
5312     endif
5313  else
5314     if (ittp .eq. 113)  then
5315        !--- write epilogue
5316        do  i = 1, mepep
5317           call gxpnbl(epepi(i), iii, l)
5318           write(iutlps, '(a)')  epepi(i)(:l)
5319        enddo
5320     else
5321        if(iclear .ne. 0) then
5322           call gclrwk(0, 1)
5323           iclear = 0
5324        endif
5325        do  i = 1, mpsep
5326           call gxpnbl(psepi(i), iii, l)
5327           write(iutlps, '(a)')  psepi(i)(:l)
5328        enddo
5329     endif
5330  endif
5331end subroutine gxwpep
5332subroutine gxwpl(np, xp1, yp1, ifill)
5333  use gxx11_common
5334  implicit none
5335  integer i,i1,i2,ierr,ifill,iforl,iii,k,kadd,l,np
5336  real f1,f2,r,v1,v2
5337  !***********************************************************************
5338  !
5339  !   Purpose: write polyline into .ps or .eps file
5340  !
5341  !--- Input
5342  !   np      number of points
5343  !   xp1      x coordinates
5344  !   yp1      y coordinates
5345  !   ifill   fill area request: 0 = no, 1 = yes
5346  !
5347  !   Author: H. Grote / CERN                        date: Apr. 27, 1995
5348  !                                              last mod: May  23, 1995
5349  !
5350  !***********************************************************************
5351
5352  real xp1(*), yp1(*)
5353  character eloc * 40, sline * (mline), style(4) * 24,              &
5354       formt1 * 24, formt2 * 24
5355  data style / '[] 0 sd', '[20] 0 sd', '[2 10] 0 sd',               &
5356       '[20 10 2 10] 0 sd' /
5357  data eloc / 'col-1 s' /
5358  data formt1 /'('' n'', 2ix, '' m'')'/
5359  data formt2 /'(2ix, '' l'')'/
5360
5361  if (istotx .gt. 0)  then
5362     write(iutlps, '(a)')  stortx(:istotx)
5363     istotx = 0
5364  endif
5365  if (iorips .eq. 1)  then
5366     v1 = xp1(1) - rx11pr(1)
5367     v2 = yp1(1) - rx11pr(3)
5368     f1 = msfact * (ibbox(3) - ibbox(1)) / (rx11pr(2) - rx11pr(1))
5369     f2 = msfact * (ibbox(4) - ibbox(2)) / (rx11pr(4) - rx11pr(3))
5370  else
5371     v1 = xp1(1) - rx11pr(1)
5372     v2 = yp1(1) - rx11pr(3)
5373     f1 = msfact * (ibbox(4) - ibbox(2)) / (rx11pr(2) - rx11pr(1))
5374     f2 = msfact * (ibbox(3) - ibbox(1)) / (rx11pr(4) - rx11pr(3))
5375  endif
5376  sline = colour(icucol)
5377  call gxpnbl(sline, iii, k)
5378  if (iorips .eq. 1)  then
5379     i1 = f1 * v1 + msfact * ibbox(2) + 0.5
5380     i2 = f2 * v2 + msfact * ibbox(1) + 0.5
5381  else
5382     i2 = f1 * v1 + msfact * ibbox(2) + 0.5
5383     i1 = f2 * v2 + msfact * ibbox(1) + 0.5
5384     i1 = msfact * ibbox(3) - i1
5385  endif
5386  call jqlwsc(ierr, r)
5387  call jqln(ierr, i)
5388  i = max(1, min(i,4))
5389  write(iutlps, '(f6.3, a, a)')  0.75 * r,                          &
5390       ' setlinewidth ', style(i)
5391  iforl =                                                           &
5392       max(log10(float(abs(i1)+1))+3., log10(float(abs(i2)+1))+3.)
5393  write(formt1(10:10), '(i1)') iforl
5394  kadd = 2 * (iforl + 2)
5395  write(sline(k+1:k+kadd), formt1)  i1, i2
5396  k = k + kadd
5397  do  i = 2, np
5398     v1 = xp1(i) - rx11pr(1)
5399     v2 = yp1(i) - rx11pr(3)
5400
5401     if (k + 16 .gt. mline)  then
5402        call gxpnbl(sline, iii, l)
5403        write(iutlps, '(a)')  sline(:l)
5404        k = 0
5405        sline = ' '
5406     endif
5407     if (iorips .eq. 1)  then
5408        i1 = f1 * v1 + msfact * ibbox(2) + 0.5
5409        i2 = f2 * v2 + msfact * ibbox(1) + 0.5
5410     else
5411        i2 = f1 * v1 + msfact * ibbox(2) + 0.5
5412        i1 = f2 * v2 + msfact * ibbox(1) + 0.5
5413        i1 = msfact * ibbox(3) - i1
5414     endif
5415     iforl =                                                         &
5416          max(log10(float(abs(i1)+1))+3., log10(float(abs(i2)+1))+3.)
5417     write(formt2(4:4), '(i1)') iforl
5418     kadd = 2 * (iforl + 1)
5419     write(sline(k+1:k+kadd), formt2)  i1, i2
5420     k = k + kadd
5421  enddo
5422  if (k .gt. 0) then
5423     call gxpnbl(sline, iii, l)
5424     write(iutlps, '(a)')  sline(:l)
5425  endif
5426  if (ifill .eq. 0)  then
5427     write(iutlps, '(a)')  eloc
5428  else
5429     write(iutlps, '(a)')  'fill ' // eloc
5430  endif
5431end subroutine gxwpl
5432subroutine gxwpm(np, xp1, yp1)
5433  use gxx11_common
5434  implicit none
5435  integer i,ifill,ip,is,j,n,np
5436  real sq21,xf,xmf,xms,xmsm,xmsq,xmsqm,xpsf,xs,xsm,xsq,xsqm,yf,ymf, &
5437       yms,ymsm,ymsq,ymsqm,ys,ysm,ysq,ysqm
5438  !***********************************************************************
5439  !
5440  !   Purpose: plot marker symbol on display and/or PostScript output
5441  !
5442  !--- Input
5443  !   np      number of marker symbols
5444  !   xp1      x coordinates
5445  !   yp1      y coordinates
5446  !
5447  !   Author: H. Grote / CERN                        date: July 6, 1995
5448  !                                              last mod: July 6, 1995
5449  !
5450  !***********************************************************************
5451
5452  parameter (xs = 0.005, ys = 0.005, sq21 = 0.4142135,              &
5453       xms = -xs, yms = -ys,                                             &
5454       xsm = 0.1 * xs, ysm = 0.1 * ys,                                   &
5455       xmsm = -xsm, ymsm = -ysm,                                         &
5456       xsq = xs * sq21, ysq = ys * sq21,                                 &
5457       xmsq = -xsq, ymsq = -ysq,                                         &
5458       xsqm = xsm * sq21, ysqm = ysm * sq21,                             &
5459       xmsqm = -xsqm, ymsqm = -ysqm )
5460  real xp1(*), yp1(*)
5461  real xsym(9,4,5), ysym(9,4,5), xlps(9), yloc(9), xlwd(9)
5462  integer nsym(4,5)
5463  character(1) dum
5464  data xsym /                                                       &
5465       xmsm, xmsm, xmsqm, xsqm, xsm, xsm, xsqm, xmsqm, xmsm, 27 * 0.,    &
5466       xms, xs, 7*0., 0., 0., 7*0., 18 * 0.,                             &
5467       xms, xs, 7*0., 0., 0., 7*0., xms, xs, 7*0., xms, xs, 7*0.,        &
5468       xms, xms, xmsq, xsq, xs, xs, xsq, xmsq, xms, 27 * 0.,             &
5469       xms, xs, 7*0., xms, xs, 7*0., 18 * 0. /
5470  data ysym /                                                       &
5471       ymsqm, ysqm, ysm, ysm, ysqm, ymsqm, ymsm, ymsm, ymsqm, 27 * 0.,   &
5472       0., 0., 7*0., ys, yms, 7*0., 18 * 0.,                             &
5473       0., 0., 7*0., ys, yms, 7*0., yms, ys, 7*0., ys, yms, 7*0.,        &
5474       ymsq, ysq, ys, ys, ysq, ymsq, yms, yms, ymsq, 27 * 0.,            &
5475       yms, ys, 7*0., ys, yms, 7*0, 18 * 0. /
5476  data nsym / 9, 0, 0, 0,                                           &
5477       2, 2, 0, 0,                                                       &
5478       2, 2, 2, 2,                                                       &
5479       9, 0, 0, 0,                                                       &
5480       2, 2, 0, 0 /
5481
5482  call gxqvar('XMETAF', i, xmf, dum)
5483  call gxqvar('YMETAF', i, ymf, dum)
5484  if (xmf .ne. 0.)  then
5485     xpsf = ymf / xmf
5486  else
5487     xpsf = 1.
5488  endif
5489  xf = rx11pr(8) * (rx11pr(2) - rx11pr(1))
5490  yf = rx11pr(8) * (rx11pr(4) - rx11pr(3))
5491  is = mod(ix11pr(4) - 1, 5) + 1
5492  if (is .eq. 1)  then
5493     ifill = 1
5494  else
5495     ifill = 0
5496  endif
5497  do  ip = 1, np
5498     do  i = 1, 4
5499        n = nsym(i,is)
5500        if (n .gt. 0)  then
5501           do  j = 1, n
5502              xlwd(j) = xp1(ip) + xf * xsym(j,i,is)
5503              yloc(j) = yp1(ip) + yf * ysym(j,i,is)
5504              xlps(j) = xp1(ip) + xpsf * xf * xsym(j,i,is)
5505           enddo
5506           if (ipseps .ne. 0)  call gxwpl(n, xlps, yloc, ifill)
5507        endif
5508     enddo
5509  enddo
5510end subroutine gxwpm
5511subroutine gxwtx(xp1, yp1, txin)
5512  use gxx11_common
5513  implicit none
5514  integer i,i1,i11,i2,i22,ia,iang1,iangle,ie,ifont,ifos,ihl,iii,    &
5515       iprec,ivl,k,lf,lint,lt,lt1,lt2,lt3,mltx,mltx2
5516  real chh,f1,f2,v1,v2,x,xp1,xup,y,yp1,yup
5517  !***********************************************************************
5518  !
5519  !   Purpose: write text with predefined font .ps or .eps file
5520  !
5521  !--- Input
5522  !   xp1      x coordinate
5523  !   yp1      y coordinate
5524  !   txin    text
5525  !
5526  !   Author: H. Grote / CERN                        date: May 10, 1995
5527  !                                              last mod: May 10, 1995
5528  !
5529  !***********************************************************************
5530
5531  parameter (mltx = 120, mltx2 = 2 * mltx)
5532  character txin * (*)
5533  character sline * (mline), txlc * (mltx2)
5534  character(24) tloc1, tloc2, tloc3, sfont(mtfont)
5535  integer ifosiz(mtfont)
5536  data sfont / '/Times-Italic', '/Times-Bold', '/Times-BoldItalic', &
5537       '/Helvetica', '/Helvetica-Oblique', '/Helvetica-Bold',            &
5538       '/Helvetica-BoldOblique', '/Courier', '/Courier-Oblique',         &
5539       '/Courier-Bold',  '/Courier-BoldOblique', '/Symbol' /
5540  data ifosiz / 1030, 1000, 1025, 930, 930,                         &
5541       930, 930, 1205, 1205, 1170, 1165, 1005 /
5542
5543  if (istotx .gt. 0)  then
5544     write(iutlps, '(a)')  stortx(:istotx)
5545     istotx = 0
5546  endif
5547  !--- copy text to local, treat ()
5548  txlc = ' '
5549  call gxpnbl(txin, iii, lint)
5550  lt = 0
5551  do  i = 1, min(mltx, lint)
5552     if(txin(i:i) .eq. '(' .or. txin(i:i) .eq. ')')  then
5553        lt = lt + 1
5554        txlc(lt:lt) = '\\'
5555     endif
5556     lt = lt + 1
5557     txlc(lt:lt) = txin(i:i)
5558  enddo
5559  call jqtxfp(ie, ifont, iprec)
5560  ifont = max(1, min(mtfont, abs(ifont)))
5561  call jqtxal(ie, ihl, ivl)
5562  call jqchh(ie, chh)
5563  call jqchup(ie, xup, yup)
5564  iang1 = atan2(-xup, yup) * 45. / atan(1.) + 0.5
5565  iangle = iang1 + (iorips - 1) * 90 + 0.5
5566  ifos = msfact * ifosiz(ifont) * chh / (rx11pr(4) - rx11pr(3))     &
5567       + 0.5
5568  if (ihl .eq. 2)  then
5569     tloc1 = ' xs 2 div'
5570     lt1 = 9
5571  elseif ( ihl .eq. 3)  then
5572     tloc1 = ' xs'
5573     lt1 = 3
5574  endif
5575  tloc2 = ' neg 0'
5576  lt2 = 6
5577  tloc3 = ' t 0 0 m'
5578  lt3 = 8
5579  call gxpnbl(sfont(ifont), iii, lf)
5580  x = xp1
5581  y = yp1 - 0.25 * (5 - ivl) * chh
5582  if (iorips .eq. 1)  then
5583     v1 = x - rx11pr(1)
5584     v2 = y - rx11pr(3)
5585     f1 = msfact * (ibbox(3) - ibbox(1)) / (rx11pr(2) - rx11pr(1))
5586     f2 = msfact * (ibbox(4) - ibbox(2)) / (rx11pr(4) - rx11pr(3))
5587  else
5588     v1 = x - rx11pr(1)
5589     v2 = y - rx11pr(3)
5590     f1 = msfact * (ibbox(4) - ibbox(2)) / (rx11pr(2) - rx11pr(1))
5591     f2 = msfact * (ibbox(3) - ibbox(1)) / (rx11pr(4) - rx11pr(3))
5592  endif
5593  !--- horizontal alignment - uses font width from font def.
5594  if (ihl .gt. 1)  then
5595     write(iutlps, '(a)')  '/xs 0 def'
5596     write(iutlps, '(a, a, a)')  '(', txlc(:lt), ')'
5597     write(iutlps, '(a, i6, a)') sfont(ifont)(:lf), ifos, ' stwn'
5598  endif
5599  sline = colour(icucol)
5600  call gxpnbl(sline, iii, k)
5601  if (iorips .eq. 1)  then
5602     i1 = f1 * v1 + msfact * ibbox(2) + 0.5
5603     i2 = f2 * v2 + msfact * ibbox(1) + 0.5
5604  else
5605     i2 = f1 * v1 + msfact * ibbox(2) + 0.5
5606     i1 = f2 * v2 + msfact * ibbox(1) + 0.5
5607     i1 = msfact * ibbox(3) - i1
5608  endif
5609  write(sline(k+1:k+10), '(2i5)')  i1, i2
5610  k = k + 10
5611  sline(k+1:k+3) = ' t '
5612  k = k + 3
5613  write(sline(k+1:k+5), '(i5)')  iangle
5614  k = k + 5
5615  sline(k+1:k+2) = ' r'
5616  k = k + 2
5617  if (ihl .gt. 1)  then
5618     sline(k+1:) =                                                   &
5619          tloc1(:lt1) // tloc2(:lt2) // tloc3(:lt3)
5620     k = k + lt1 + lt2 + lt3
5621  endif
5622  sline(k+1:) = ' 0 0 m'
5623  write(iutlps, '(a)')  sline(:k)
5624  write(iutlps, '(a, a, i6, a)')  sfont(ifont)(:lf), ' fft ',       &
5625       ifos, ' sf 0 0 m'
5626  write(iutlps, '(a, a, a)')  '(', txlc(:lt), ')'
5627  sline = 'show'
5628  k = 4
5629  tloc2 = ' 0'
5630  lt2 = 2
5631  if (ihl .gt. 1)  then
5632     sline(k+1:) =                                                   &
5633          tloc1(:lt1) // tloc2(:lt2) // tloc3(:lt3)
5634     k = k + lt1 + lt2 + lt3
5635  endif
5636  ia = -iangle
5637  write(sline(k+1:k+6), '(i6)')  ia
5638  k = k + 6
5639  sline(k+1:k+2) = ' r'
5640  k = k + 2
5641  i11 = -i1
5642  i22 = -i2
5643  write(sline(k+1:k+12), '(2i6)')  i11, i22
5644  k = k + 12
5645  sline(k+1:k+2) = ' t'
5646  k = k + 2
5647  write(iutlps, '(a)')  sline(:k)
5648end subroutine gxwtx
5649subroutine jqmk(ierr, i1)
5650  use gxx11_common
5651  use gxx11_aux
5652  implicit none
5653  integer ierr,i1
5654  ierr = 0
5655  i1 = ivals(1)
5656end subroutine jqmk
5657subroutine jqfais(ierr, i1)
5658  use gxx11_common
5659  use gxx11_aux
5660  implicit none
5661  integer ierr,i1
5662  ierr = 0
5663  i1 = ivals(2)
5664end subroutine jqfais
5665subroutine jqtxal(ierr, i1, i2)
5666  use gxx11_common
5667  use gxx11_aux
5668  implicit none
5669  integer ierr, i1,i2
5670  ierr = 0
5671  i1 = ivals(3)
5672  i2 = ivals(4)
5673end subroutine jqtxal
5674subroutine jqtxfp(ierr, i1, i2)
5675  use gxx11_common
5676  use gxx11_aux
5677  implicit none
5678  integer ierr, i1,i2
5679  ierr = 0
5680  i1 = ivals(5)
5681  i2 = ivals(6)
5682end subroutine jqtxfp
5683subroutine jqpmci(ierr, i1)
5684  use gxx11_common
5685  use gxx11_aux
5686  implicit none
5687  integer ierr, i1
5688  ierr = 0
5689  i1 = ivals(7)
5690end subroutine jqpmci
5691subroutine jswks(i1)
5692  use gxx11_common
5693  use gxx11_aux
5694  implicit none
5695  integer i1
5696  ivals(8) = i1
5697end subroutine jswks
5698subroutine jqwks(i1, ierr, i2)
5699  use gxx11_common
5700  use gxx11_aux
5701  implicit none
5702  integer ierr, i1,i2
5703  ierr = 0
5704  i2 = ivals(8)
5705end subroutine jqwks
5706subroutine jqchup(ierr, r1, r2)
5707  use gxx11_common
5708  use gxx11_aux
5709  implicit none
5710  integer ierr
5711  real r1,r2
5712  ierr = 0
5713  r1 = rvals(1)
5714  r2 = rvals(2)
5715end subroutine jqchup
5716subroutine jqchh(ierr, r1)
5717  use gxx11_common
5718  use gxx11_aux
5719  implicit none
5720  integer ierr
5721  real r1
5722  ierr = 0
5723  r1 = rvals(3)
5724end subroutine jqchh
5725subroutine jqtxci(ierr, i1)
5726  use gxx11_common
5727  use gxx11_aux
5728  implicit none
5729  integer ierr,i1
5730  ierr = 0
5731  i1 = ivals(9)
5732end subroutine jqtxci
5733subroutine jqnt(i1, ierr, ar1, ar2)
5734  use gxx11_common
5735  use gxx11_aux
5736  implicit none
5737  integer ierr,i1,i
5738  real ar1(4), ar2(4)
5739  ierr = 0
5740  do  i = 1, 4
5741     ar1(i) = rvals(i+3)
5742     ar2(i) = rvals(i+7)
5743  enddo
5744end subroutine jqnt
5745subroutine jqmksc(ierr, r1)
5746  use gxx11_common
5747  use gxx11_aux
5748  implicit none
5749  integer ierr
5750  real r1
5751  ierr = 0
5752  r1 = rvals(14)
5753end subroutine jqmksc
5754subroutine jsvp(i1, r1, r2, r3, r4)
5755  use gxx11_common
5756  use gxx11_aux
5757  implicit none
5758  integer i1
5759  real r1,r2,r3,r4
5760  rvals(8) = r1
5761  rvals(9) = r2
5762  rvals(10) = r3
5763  rvals(11) = r4
5764end subroutine jsvp
5765subroutine jqplci(ierr, i1)
5766  use gxx11_common
5767  use gxx11_aux
5768  implicit none
5769  integer ierr,i1
5770  ierr = 0
5771  i1 = ivals(11)
5772end subroutine jqplci
5773subroutine jschxp(r1)
5774  use gxx11_common
5775  use gxx11_aux
5776  implicit none
5777  real r1
5778  rvals(12) = r1
5779end subroutine jschxp
5780subroutine jqchxp(ierr, r1)
5781  use gxx11_common
5782  use gxx11_aux
5783  implicit none
5784  integer ierr
5785  real r1
5786  ierr = 0
5787  r1 = rvals(12)
5788end subroutine jqchxp
5789subroutine jqlwsc(ierr, r1)
5790  use gxx11_common
5791  use gxx11_aux
5792  implicit none
5793  integer ierr
5794  real r1
5795  ierr = 0
5796  r1 = rvals(13)
5797end subroutine jqlwsc
5798subroutine jqln(ierr, i1)
5799  use gxx11_common
5800  use gxx11_aux
5801  implicit none
5802  integer ierr,i1
5803  ierr = 0
5804  i1 = ivals(12)
5805end subroutine jqln
5806subroutine jqcntn(ierr, i1)
5807  use gxx11_common
5808  use gxx11_aux
5809  implicit none
5810  integer ierr,i1
5811  ierr = 0
5812  i1 = ivals(13)
5813end subroutine jqcntn
5814subroutine gclrwk(i1, i2)
5815  use gxx11_common
5816  use gxx11_aux
5817  implicit none
5818  integer i1,i2
5819  if (ipseps .eq. 1)  call gxwclr(i1, i2)
5820end subroutine gclrwk
5821subroutine gtx(r1, r2, string)
5822  use gxx11_common
5823  use gxx11_aux
5824  implicit none
5825  real r1,r2
5826  character(*) string
5827  if (ipseps .ne. 0)  call gxwtx(r1, r2, string)
5828end subroutine gtx
5829subroutine gfa(i1, ar1, ar2)
5830  use gxx11_common
5831  use gxx11_aux
5832  implicit none
5833  integer i1
5834  real ar1(*),ar2(*)
5835  if (ipseps .ne. 0)  call gxwpl(i1, ar1, ar2, ivals(2))
5836end subroutine gfa
5837subroutine gpl(i1, ar1, ar2)
5838  use gxx11_common
5839  use gxx11_aux
5840  implicit none
5841  integer i1
5842  real ar1(*),ar2(*)
5843  if (ipseps .ne. 0)  call gxwpl(i1, ar1, ar2, 0)
5844end subroutine gpl
5845subroutine jsmk(i1)
5846  use gxx11_common
5847  use gxx11_aux
5848  implicit none
5849  integer i1
5850  ivals(1) = i1
5851  ix11pr(4) = i1
5852end subroutine jsmk
5853subroutine jsfais(i1)
5854  use gxx11_common
5855  use gxx11_aux
5856  implicit none
5857  integer i1
5858  ivals(2) = i1
5859end subroutine jsfais
5860subroutine jstxal(i1, i2)
5861  use gxx11_common
5862  use gxx11_aux
5863  implicit none
5864  integer i1,i2
5865  ivals(3) = i1
5866  ivals(4) = i2
5867  ix11pr(1) = i1
5868  ix11pr(2) = i2
5869end subroutine jstxal
5870subroutine jstxfp(i1, i2)
5871  use gxx11_common
5872  use gxx11_aux
5873  implicit none
5874  integer i1,i2
5875  ivals(5) = i1
5876  ivals(6) = i2
5877end subroutine jstxfp
5878subroutine jspmci(i1)
5879  use gxx11_common
5880  use gxx11_aux
5881  implicit none
5882  integer i1
5883  ivals(7) = i1
5884  ivals(14) = 0
5885end subroutine jspmci
5886subroutine jschup(r1, r2)
5887  use gxx11_common
5888  use gxx11_aux
5889  implicit none
5890  real r1,r2
5891  rvals(1) = r1
5892  rvals(2) = r2
5893  rx11pr(5) = r1
5894  rx11pr(6) = r2
5895end subroutine jschup
5896subroutine jschh(r1)
5897  use gxx11_common
5898  use gxx11_aux
5899  implicit none
5900  real r1
5901  rvals(3) = r1
5902  rx11pr(7) = r1
5903end subroutine jschh
5904subroutine jstxci(i1)
5905  use gxx11_common
5906  use gxx11_aux
5907  implicit none
5908  integer i1
5909  ivals(9) = i1
5910  ivals(14) = 0
5911end subroutine jstxci
5912subroutine jsmksc(r1)
5913  use gxx11_common
5914  use gxx11_aux
5915  implicit none
5916  real r1
5917  rvals(14) = r1
5918  rx11pr(8) = r1
5919end subroutine jsmksc
5920subroutine jswn(i1, r1, r2, r3, r4)
5921  use gxx11_common
5922  use gxx11_aux
5923  implicit none
5924  integer i1
5925  real r1,r2,r3,r4
5926  rvals(4) = r1
5927  rvals(5) = r2
5928  rvals(6) = r3
5929  rvals(7) = r4
5930  rx11pr(1) = r1
5931  rx11pr(2) = r2
5932  rx11pr(3) = r3
5933  rx11pr(4) = r4
5934  if (r2 .gt. r1)  then
5935     fxpix = nxpix / (r2 - r1)
5936  else
5937     fxpix = 1.
5938  endif
5939  if (r4 .gt. r3)  then
5940     fypix = nypix / (r4 - r3)
5941  else
5942     fypix = 1.
5943  endif
5944end subroutine jswn
5945subroutine jsplci(i1)
5946  use gxx11_common
5947  use gxx11_aux
5948  implicit none
5949  integer i1
5950  ivals(11) = i1
5951  ivals(14) = 0
5952end subroutine jsplci
5953subroutine jslwsc(r1)
5954  use gxx11_common
5955  use gxx11_aux
5956  implicit none
5957  real r1
5958  rvals(13) = r1
5959end subroutine jslwsc
5960subroutine jsln(i1)
5961  use gxx11_common
5962  use gxx11_aux
5963  implicit none
5964  integer i1,iz
5965  ivals(12) = i1
5966  iz = i1 - 1
5967end subroutine jsln
5968subroutine jslctp(i1)
5969  use gxx11_common
5970  use gxx11_aux
5971  implicit none
5972  integer i1
5973  ivals(14) = i1
5974end subroutine jslctp
5975subroutine jqlctp(i1)
5976  use gxx11_common
5977  use gxx11_aux
5978  implicit none
5979  integer i1
5980  i1 = ivals(14)
5981end subroutine jqlctp
5982subroutine wacwk(iw)
5983  use gxx11_common
5984  implicit none
5985  integer iw
5986  !***********************************************************************
5987  !
5988  !   Purpose: Activate workstation
5989  !
5990  !--- Input
5991  !   iw       workstation number
5992  !   Author: H. Grote / CERN                        date: Jan. 25, 1994
5993  !                                           last mod: Jan. 25, 1994
5994  !***********************************************************************
5995
5996  if (iw .gt. 0 .and. iw .le. mx11tf)  then
5997     ix11tf(iw) = 1
5998  endif
5999end subroutine wacwk
6000subroutine wclks
6001  implicit none
6002  !***********************************************************************
6003  !
6004  !   Purpose: Close X11 package
6005  !
6006  !   Author: H. Grote / CERN                        date: Jan. 25, 1994
6007  !                                           last mod: Jan. 25, 1994
6008  !***********************************************************************
6009end subroutine wclks
6010subroutine wclwk(iw)
6011  use gxx11_common
6012  implicit none
6013  integer iw
6014  !***********************************************************************
6015  !
6016  !   Purpose: Close workstation
6017  !
6018  !--- Input
6019  !   iw       workstation number
6020  !   Author: H. Grote / CERN                        date: Jan. 25, 1994
6021  !                                           last mod: Jan. 25, 1994
6022  !***********************************************************************
6023
6024end subroutine wclwk
6025subroutine wdawk(iw)
6026  use gxx11_common
6027  implicit none
6028  integer iw
6029  !***********************************************************************
6030  !
6031  !   Purpose: Deactivate workstation
6032  !
6033  !--- Input
6034  !   iw       workstation number
6035  !   Author: H. Grote / CERN                        date: Jan. 25, 1994
6036  !                                           last mod: Jan. 25, 1994
6037  !***********************************************************************
6038
6039  if (iw .gt. 0 .and. iw .le. mx11tf)  then
6040     ix11tf(iw) = 0
6041  endif
6042end subroutine wdawk
6043subroutine wopks(ieu, idum)
6044  use gxx11_common
6045  implicit none
6046  integer i,idum,ieu
6047  !***********************************************************************
6048  !
6049  !   Purpose: Open X11 package
6050  !
6051  !--- Input
6052  !   ieu      error file unit (not used)
6053  !   idum     dummy
6054  !   Author: H. Grote / CERN                        date: Jan. 25, 1994
6055  !                                           last mod: Jan. 25, 1994
6056  !***********************************************************************
6057
6058  !--- preset workstations to inactive and closed
6059  do  i = 1, mx11tf
6060     ix11tf(i) = 0
6061     ix11op(i) = 0
6062  enddo
6063end subroutine wopks
6064logical function affirm(sus)
6065  implicit none
6066  character(1) sus
6067  affirm = sus.eq.'y'.or.sus.eq.'Y'.or.sus.eq.'o'.or.sus.eq.'O'
6068end function affirm
6069subroutine wopwk(iw, icont, it)
6070  use gxx11_common
6071  implicit none
6072  integer icont,it,iw
6073  !      integer ix,iy
6074  !      real r
6075  !***********************************************************************
6076  !
6077  !   Purpose: Open workstation
6078  !
6079  !--- Input
6080  !   iw       workstation number
6081  !   icont    dummy
6082  !   it       dummy
6083  !   Author: H. Grote / CERN                        date: Jan. 25, 1994
6084  !                                           last mod: Jan. 25, 1994
6085  !***********************************************************************
6086
6087end subroutine wopwk
Note: See TracBrowser for help on using the repository browser.