source: LMDZ6/branches/Amaury_dev/libf/misc/xersve.f90 @ 5112

Last change on this file since 5112 was 5106, checked in by abarral, 2 months ago

Turn coefils.h into lmdz_coefils.f90
Put filtreg.F90 inside lmdz_filtreg.F90
Turn mod_filtreg_p.F90 into lmdz_filtreg_p.F90
Delete obsolete parafilt.h*
(lint) remove spaces between routine name and args

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 4.7 KB
Line 
1!DECK XERSVE
2SUBROUTINE XERSVE(LIBRAR, SUBROU, MESSG, KFLAG, NERR, LEVEL, &
3        ICOUNT)
4  IMPLICIT NONE
5  !***BEGIN PROLOGUE  XERSVE
6  !***SUBSIDIARY
7  !***PURPOSE  Record that an error has occurred.
8  !***LIBRARY   SLATEC (XERROR)
9  !***CATEGORY  R3
10  !***TYPE      ALL (XERSVE-A)
11  !***KEYWORDS  ERROR, XERROR
12  !***AUTHOR  Jones, R. E., (SNLA)
13  !***DESCRIPTION
14  !
15  ! *Usage:
16  !
17  !    INTEGER  KFLAG, NERR, LEVEL, ICOUNT
18  !    CHARACTER * (len) LIBRAR, SUBROU, MESSG
19  !
20  !    CALL XERSVE (LIBRAR, SUBROU, MESSG, KFLAG, NERR, LEVEL, ICOUNT)
21  !
22  ! *Arguments:
23  !
24  !    LIBRAR :IN    is the library that the message is from.
25  !    SUBROU :IN    is the SUBROUTINE that the message is from.
26  !    MESSG  :IN    is the message to be saved.
27  !    KFLAG  :IN    indicates the action to be performed.
28  !                  when KFLAG > 0, the message in MESSG is saved.
29  !                  when KFLAG=0 the tables will be dumped and
30  !                  cleared.
31  !                  when KFLAG < 0, the tables will be dumped and
32  !                  not cleared.
33  !    NERR   :IN    is the error number.
34  !    LEVEL  :IN    is the error severity.
35  !    ICOUNT :OUT   the number of times this message has been seen,
36  !                  or zero if the table has overflowed and does not
37  !                  contain this message specifically.  When KFLAG=0,
38  !                  ICOUNT will not be altered.
39  !
40  ! *Description:
41  !
42  !   Record that this error occurred and possibly dump and clear the
43  !   tables.
44  !
45  !***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
46  !             Error-handling Package, SAND82-0800, Sandia
47  !             Laboratories, 1982.
48  !***ROUTINES CALLED  I1MACH, XGETUA
49  !***REVISION HISTORY  (YYMMDD)
50  !   800319  DATE WRITTEN
51  !   861211  REVISION DATE from Version 3.2
52  !   891214  Prologue converted to Version 4.0 format.  (BAB)
53  !   900413  Routine modified to remove reference to KFLAG.  (WRB)
54  !   900510  Changed to add LIBRARY NAME and SUBROUTINE to calling
55  !       sequence, use IF-THEN-ELSE, make number of saved entries
56  !       easily changeable, changed routine name from XERSAV to
57  !       XERSVE.  (RWC)
58  !   910626  Added LIBTAB and SUBTAB to SAVE statement.  (BKS)
59  !   920501  Reformatted the REFERENCES section.  (WRB)
60  !***END PROLOGUE  XERSVE
61  INTEGER,PARAMETER :: LENTAB=10
62  INTEGER :: LUN(5)
63  CHARACTER(len=*) :: LIBRAR, SUBROU, MESSG
64  CHARACTER(len=8) :: LIBTAB(LENTAB), SUBTAB(LENTAB), LIB, SUB
65  CHARACTER(len=20) :: MESTAB(LENTAB), MES
66  DIMENSION NERTAB(LENTAB), LEVTAB(LENTAB), KOUNT(LENTAB)
67  SAVE LIBTAB, SUBTAB, MESTAB, NERTAB, LEVTAB, KOUNT, KOUNTX, NMSG
68  DATA KOUNTX/0/, NMSG/0/
69  INTEGER :: NERR,LEVEL,KONTRL
70  INTEGER :: NERTAB, LEVTAB, KOUNT, KOUNTX, NMSG
71  INTEGER :: KFLAG, ICOUNT, NUNIT, KUNIT, IUNIT, I1MACH, I
72  !***FIRST EXECUTABLE STATEMENT  XERSVE
73  !
74  IF (KFLAG<=0) THEN
75  !
76  !    Dump the table.
77  !
78     IF (NMSG==0) RETURN
79  !
80  !    Print to each unit.
81  !
82     CALL XGETUA (LUN, NUNIT)
83     DO KUNIT = 1,NUNIT
84        IUNIT = LUN(KUNIT)
85        IF (IUNIT==0) IUNIT = I1MACH(4)
86  !
87  !       Print the table header.
88  !
89        WRITE (IUNIT,9000)
90  !
91  !       Print body of table.
92  !
93        DO I = 1,NMSG
94           WRITE (IUNIT,9010) LIBTAB(I), SUBTAB(I), MESTAB(I), &
95                 NERTAB(I),LEVTAB(I),KOUNT(I)
96  END DO
97  !
98  !       Print number of other errors.
99  !
100        IF (KOUNTX/=0) WRITE (IUNIT,9020) KOUNTX
101        WRITE (IUNIT,9030)
102  END DO
103  !
104  !    Clear the error tables.
105  !
106     IF (KFLAG==0) THEN
107        NMSG = 0
108        KOUNTX = 0
109     ENDIF
110  ELSE
111  !
112  !    PROCESS A MESSAGE...
113  !    SEARCH FOR THIS MESSG, OR ELSE AN EMPTY SLOT FOR THIS MESSG,
114  !    OR ELSE DETERMINE THAT THE ERROR TABLE IS FULL.
115  !
116     LIB = LIBRAR
117     SUB = SUBROU
118     MES = MESSG
119     DO I = 1,NMSG
120        IF (LIB==LIBTAB(I) .AND. SUB==SUBTAB(I) .AND. &
121              MES==MESTAB(I) .AND. NERR==NERTAB(I) .AND. &
122              LEVEL==LEVTAB(I)) THEN
123              KOUNT(I) = KOUNT(I) + 1
124              ICOUNT = KOUNT(I)
125              RETURN
126        ENDIF
127  END DO
128  !
129     IF (NMSG<LENTAB) THEN
130  !
131  !       Empty slot found for new message.
132  !
133        NMSG = NMSG + 1
134        LIBTAB(I) = LIB
135        SUBTAB(I) = SUB
136        MESTAB(I) = MES
137        NERTAB(I) = NERR
138        LEVTAB(I) = LEVEL
139        KOUNT (I) = 1
140        ICOUNT    = 1
141     ELSE
142  !
143  !       Table is full.
144  !
145        KOUNTX = KOUNTX+1
146        ICOUNT = 0
147     ENDIF
148  ENDIF
149  RETURN
150  !
151  ! Formats.
152  !
153 9000   FORMAT ('0          ERROR MESSAGE SUMMARY' / &
154              ' LIBRARY    SUBROUTINE MESSAGE START             NERR', &
155              '     LEVEL     COUNT')
156 9010   FORMAT (1X,A,3X,A,3X,A,3I10)
157 9020   FORMAT ('0OTHER ERRORS NOT INDIVIDUALLY TABULATED = ', I10)
158 9030   FORMAT (1X)
159END SUBROUTINE XERSVE
Note: See TracBrowser for help on using the repository browser.