Ignore:
Timestamp:
Jul 23, 2024, 7:14:34 PM (8 weeks ago)
Author:
abarral
Message:

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/misc/xercnt.f90

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