1 | !DECK XGETUA |
---|
2 | SUBROUTINE XGETUA (IUNITA, N) |
---|
3 | IMPLICIT NONE |
---|
4 | !***BEGIN PROLOGUE XGETUA |
---|
5 | !***PURPOSE Return unit number(s) to which error messages are being |
---|
6 | ! sent. |
---|
7 | !***LIBRARY SLATEC (XERROR) |
---|
8 | !***CATEGORY R3C |
---|
9 | !***TYPE ALL (XGETUA-A) |
---|
10 | !***KEYWORDS ERROR, XERROR |
---|
11 | !***AUTHOR Jones, R. E., (SNLA) |
---|
12 | !***DESCRIPTION |
---|
13 | ! |
---|
14 | ! Abstract |
---|
15 | ! XGETUA may be called to determine the unit number or numbers |
---|
16 | ! to which error messages are being sent. |
---|
17 | ! These unit numbers may have been set by a call to XSETUN, |
---|
18 | ! or a call to XSETUA, or may be a default value. |
---|
19 | ! |
---|
20 | ! Description of Parameters |
---|
21 | ! --Output-- |
---|
22 | ! IUNIT - an array of one to five unit numbers, depending |
---|
23 | ! on the value of N. A value of zero refers to the |
---|
24 | ! default unit, as defined by the I1MACH machine |
---|
25 | ! constant routine. Only IUNIT(1),...,IUNIT(N) are |
---|
26 | ! defined by XGETUA. The values of IUNIT(N+1),..., |
---|
27 | ! IUNIT(5) are not defined (for N .LT. 5) or altered |
---|
28 | ! in any way by XGETUA. |
---|
29 | ! N - the number of units to which copies of the |
---|
30 | ! error messages are being sent. N will be in the |
---|
31 | ! range from 1 to 5. |
---|
32 | ! |
---|
33 | !***REFERENCES R. E. Jones and D. K. Kahaner, XERROR, the SLATEC |
---|
34 | ! Error-handling Package, SAND82-0800, Sandia |
---|
35 | ! Laboratories, 1982. |
---|
36 | !***ROUTINES CALLED J4SAVE |
---|
37 | !***REVISION HISTORY (YYMMDD) |
---|
38 | ! 790801 DATE WRITTEN |
---|
39 | ! 861211 REVISION DATE from Version 3.2 |
---|
40 | ! 891214 Prologue converted to Version 4.0 format. (BAB) |
---|
41 | ! 920501 Reformatted the REFERENCES section. (WRB) |
---|
42 | !***END PROLOGUE XGETUA |
---|
43 | DIMENSION IUNITA(5) |
---|
44 | INTEGER :: IUNITA, N, J4SAVE, INDEX, I |
---|
45 | !***FIRST EXECUTABLE STATEMENT XGETUA |
---|
46 | N = J4SAVE(5,0,.FALSE.) |
---|
47 | DO I=1,N |
---|
48 | INDEX = I+4 |
---|
49 | IF (I.EQ.1) INDEX = 3 |
---|
50 | IUNITA(I) = J4SAVE(INDEX,0,.FALSE.) |
---|
51 | END DO |
---|
52 | RETURN |
---|
53 | END SUBROUTINE XGETUA |
---|