All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
pxpriv.f
Go to the documentation of this file.
1 CDECK ID>, PXPRIV.
2  SUBROUTINE pxpriv (NAME,NELMT,IARR)
3 *.*********************************************************
4 *. ------
5 *. PXPRIV
6 *. ------
7 *. SOURCE: J.W.Gary
8 *. Print-out of an integer vector array
9 *. Usage:
10 *.
11 *. CHARACTER*6 NAME
12 *. INTEGER NELMT
13 *. PARAMETER (NELMT=1.or.more)
14 *. INTEGER IARR (NELMT)
15 *. INTEGER ISIZ
16 *.
17 *. NAME = 'IARR '
18 *. ISIZ = 1.to.NELMT
19 *. CALL PXPRIV (NAME,ISIZ,IARR)
20 *.
21 *. INPUT : NAME The six character name of the vector
22 *. INPUT : ISIZ The number of elements to print
23 *. INPUT : IARR The integer vector array
24 *.
25 *.*********************************************************
26  IMPLICIT NONE
27  INTEGER iarr (*),iarrem (10)
28  INTEGER nelmt,nrow,ir,ic,ncol,nrem
29  CHARACTER*(*) name
30  nrow = nelmt / 10
31  nrem = mod(nelmt,10)
32  IF (nrem.NE.0) THEN
33  DO 110 ic = 1,10
34  iarrem(ic) = 0
35  IF (ic.LE.nrem) iarrem(ic) = iarr(nrow*10+ic)
36  110 CONTINUE
37  nrow = nrow + 1
38  END IF
39  ncol = 10
40  WRITE (6,fmt='('' Array name: '',A6)') name
41  DO 120 ir = 1,nrow
42  IF (ir.EQ.nrow.AND.nrem.NE.0) THEN
43  ncol = nrem
44  WRITE (6,fmt='(I4,'': '',10I6)')
45  + ir,(iarrem(ic),ic=1,ncol)
46  ELSE
47  WRITE (6,fmt='(I4,'': '',10I6)')
48  + ir,(iarr((ir-1)*10+ic),ic=1,ncol)
49  END IF
50  120 CONTINUE
51  RETURN
52  END
subroutine pxpriv(NAME, NELMT, IARR)
Definition: pxpriv.f:2
virtual const std::string & name() const