source: LMDZ6/branches/Amaury_dev/libf/misc/xercnt.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: 2.5 KB
Line 
1!DECK XERCNT
2SUBROUTINE XERCNT(LIBRAR, SUBROU, MESSG, NERR, LEVEL, KONTRL)
3  IMPLICIT NONE
4  !***BEGIN PROLOGUE  XERCNT
5  !***SUBSIDIARY
6  !***PURPOSE  Allow user control over handling of errors.
7  !***LIBRARY   SLATEC (XERROR)
8  !***CATEGORY  R3C
9  !***TYPE      ALL (XERCNT-A)
10  !***KEYWORDS  ERROR, XERROR
11  !***AUTHOR  Jones, R. E., (SNLA)
12  !***DESCRIPTION
13  !
14  ! Abstract
15  !    Allows user control over handling of individual errors.
16  !    Just after each message is recorded, but before it is
17  !    processed any further (i.e., before it is printed or
18  !    a decision to abort is made), a CALL is made to XERCNT.
19  !    If the user has provided his own version of XERCNT, he
20  !    can then override the value of KONTROL used in processing
21  !    this message by redefining its value.
22  !    KONTRL may be set to any value from -2 to 2.
23  !    The meanings for KONTRL are the same as in XSETF, except
24  !    that the value of KONTRL changes only for this message.
25  !    If KONTRL is set to a value outside the range from -2 to 2,
26  !    it will be moved back into that range.
27  !
28  ! Description of Parameters
29  !
30  !  --Input--
31  !    LIBRAR - the library that the routine is in.
32  !    SUBROU - the SUBROUTINE that XERMSG is being called from
33  !    MESSG  - the first 20 characters of the error message.
34  !    NERR   - same as in the CALL to XERMSG.
35  !    LEVEL  - same as in the CALL to XERMSG.
36  !    KONTRL - the current value of the control flag as set
37  !             by a CALL to XSETF.
38  !
39  !  --Output--
40  !    KONTRL - the new value of KONTRL.  If KONTRL is not
41  !             defined, it will remain at its original value.
42  !             This changed value of control affects only
43  !             the current occurrence of the current message.
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  (NONE)
49  !***REVISION HISTORY  (YYMMDD)
50  !   790801  DATE WRITTEN
51  !   861211  REVISION DATE from Version 3.2
52  !   891214  Prologue converted to Version 4.0 format.  (BAB)
53  !   900206  Routine changed from user-callable to subsidiary.  (WRB)
54  !   900510  Changed calling sequence to include LIBRARY and SUBROUTINE
55  !       names, changed routine name from XERCTL to XERCNT.  (RWC)
56  !   920501  Reformatted the REFERENCES section.  (WRB)
57  !***END PROLOGUE  XERCNT
58  CHARACTER(len=*) :: LIBRAR, SUBROU, MESSG
59  INTEGER :: NERR, LEVEL, KONTRL
60  !***FIRST EXECUTABLE STATEMENT  XERCNT
61
62END SUBROUTINE XERCNT
Note: See TracBrowser for help on using the repository browser.