source: LMDZ6/trunk/libf/misc/xerhlt.f90 @ 5300

Last change on this file since 5300 was 5246, checked in by abarral, 11 days ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

  • 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: 1.4 KB
Line 
1!DECK XERHLT
2SUBROUTINE XERHLT (MESSG)
3  !***BEGIN PROLOGUE  XERHLT
4  !***SUBSIDIARY
5  !***PURPOSE  Abort program execution and print error message.
6  !***LIBRARY   SLATEC (XERROR)
7  !***CATEGORY  R3C
8  !***TYPE      ALL (XERHLT-A)
9  !***KEYWORDS  ABORT PROGRAM EXECUTION, ERROR, XERROR
10  !***AUTHOR  Jones, R. E., (SNLA)
11  !***DESCRIPTION
12  !
13  ! Abstract
14  !    ***Note*** machine dependent routine
15  !    XERHLT aborts the execution of the program.
16  !    The error message causing the abort is given in the calling
17  !    sequence, in case one needs it for printing on a dayfile,
18  !    for example.
19  !
20  ! Description of Parameters
21  !    MESSG is as in XERMSG.
22  !
23  !***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
24  !             Error-handling Package, SAND82-0800, Sandia
25  !             Laboratories, 1982.
26  !***ROUTINES CALLED  (NONE)
27  !***REVISION HISTORY  (YYMMDD)
28  !   790801  DATE WRITTEN
29  !   861211  REVISION DATE from Version 3.2
30  !   891214  Prologue converted to Version 4.0 format.  (BAB)
31  !   900206  Routine changed from user-callable to subsidiary.  (WRB)
32  !   900510  Changed calling sequence to delete length of character
33  !       and changed routine name from XERABT to XERHLT.  (RWC)
34  !   920501  Reformatted the REFERENCES section.  (WRB)
35  !***END PROLOGUE  XERHLT
36  CHARACTER(len=*) :: MESSG
37  !***FIRST EXECUTABLE STATEMENT  XERHLT
38  STOP
39END SUBROUTINE XERHLT
Note: See TracBrowser for help on using the repository browser.