GBTOlib: library for evaluation of molecular integrals in mixed Gaussian / B-spline basis  111
Functions/Subroutines
utils Module Reference

Functions/Subroutines

real(kind=wp) function D1MACH (I)
 
real(kind=ep1) function Q1MACH (I)
 
subroutine FDUMP
 
integer function I1MACH (I)
 
function J4SAVE (IWHICH, IVALUE, ISET)
 
function R1MACH (I)
 
subroutine XERCNT (LIBRAR, SUBROU, MESSG, NERR, LEVEL, KONTRL)
 
subroutine XERHLT (MESSG)
 
subroutine XERMSG (LIBRAR, SUBROU, MESSG, NERR, LEVEL)
 
subroutine XERPRN (PREFIX, NPREF, MESSG, NWRAP)
 
subroutine XERSVE (LIBRAR, SUBROU, MESSG, KFLAG, NERR, LEVEL, ICOUNT)
 
subroutine XGETUA (IUNITA, N)
 
subroutine XERCLR
 *DECK XERCLR ***BEGIN PROLOGUE XERCLR ***PURPOSE Reset current error number to zero. ***LIBRARY SLATEC (XERROR) ***CATEGORY R3C ***TYPE ALL (XERCLR-A) ***KEYWORDS ERROR, XERROR ***AUTHOR Jones, R. E., (SNLA) ***DESCRIPTION More...
 
logical function search_string (unit_no, string, rew, fmted)
 This function searches an input unit for the given string and returns the logical value .true. if the string has been found. In that case the input unit is positioned one line after the sought string. If the string is not found then the returned value is .false. and the input unit is positioned at its end. More...
 

Detailed Description

Todo:
rewrite xermsg using variables defined as private in this module and get rid of the helper routines that cause the doxygen graphs to be very messy!!!

Function/Subroutine Documentation

◆ D1MACH()

real(kind=wp) function utils::D1MACH (   I)
***PURPOSE  Return floating point machine dependent constants.
***LIBRARY   SLATEC
***CATEGORY  R1
***TYPE      DOUBLE PRECISION (R1MACH-S, D1MACH-D)
***KEYWORDS  MACHINE CONSTANTS
***AUTHOR  Fox, P. A., (Bell Labs)
           Hall, A. D., (Bell Labs)
           Schryer, N. L., (Bell Labs)
***DESCRIPTION

   D1MACH can be used to obtain machine-dependent parameters for the
   local machine environment.  It is a function subprogram with one
   (input) argument, and can be referenced as follows:

        D = D1MACH(I)

   where I=1,...,5.  The (output) value of D above is determined by
   the (input) value of I.  The results for various values of I are
   discussed below.

   D1MACH( 1) = B**(EMIN-1), the smallest positive magnitude.
   D1MACH( 2) = B**EMAX*(1 - B**(-T)), the largest magnitude.
   D1MACH( 3) = B**(-T), the smallest relative spacing.
   D1MACH( 4) = B**(1-T), the largest relative spacing.
   D1MACH( 5) = LOG10(B)

   Assume double precision numbers are represented in the T-digit,
   base-B form

              sign (B**E)*( (X(1)/B) + ... + (X(T)/B**T) )

   where 0 .LE. X(I) .LT. B for I=1,...,T, 0 .LT. X(1), and
   EMIN .LE. E .LE. EMAX.

   The values of B, T, EMIN and EMAX are provided in I1MACH as
   follows:
   I1MACH(10) = B, the base.
   I1MACH(14) = T, the number of base-B digits.
   I1MACH(15) = EMIN, the smallest exponent E.
   I1MACH(16) = EMAX, the largest exponent E.

   To alter this function for a particular environment, the desired
   set of DATA statements should be activated by removing the C from
   column 1.  Also, the values of D1MACH(1) - D1MACH(4) should be
   checked for consistency with the local operating system.

***REFERENCES  P. A. Fox, A. D. Hall and N. L. Schryer, Framework for
                 a portable library, ACM Transactions on Mathematical
                 Software 4, 2 (June 1978), pp. 177-188.
***ROUTINES CALLED  XERMSG
***REVISION HISTORY  (YYMMDD)
   750101  DATE WRITTEN
   890213  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)
   900315  CALLs to XERROR changed to CALLs to XERMSG.  (THJ)
   900618  Added DEC RISC constants.  (WRB)
   900723  Added IBM RS 6000 constants.  (WRB)
   900911  Added SUN 386i constants.  (WRB)
   910710  Added HP 730 constants.  (SMR)
   911114  Added Convex IEEE constants.  (WRB)
   920121  Added SUN -r8 compiler option constants.  (WRB)
   920229  Added Touchstone Delta i860 constants.  (WRB)
   920501  Reformatted the REFERENCES section.  (WRB)
   920625  Added CONVEX -p8 and -pd8 compiler option constants.
           (BKS, WRB)
   930201  Added DEC Alpha and SGI constants.  (RWC and WRB)
   121204  Hard-coded constants replaced by FORTRAN intrinsic functions (Z.Masin)

***FIRST EXECUTABLE STATEMENT D1MACH

◆ FDUMP()

subroutine utils::FDUMP
***PURPOSE  Symbolic dump (should be locally written).
***LIBRARY   SLATEC (XERROR)
***CATEGORY  R3
***TYPE      ALL (FDUMP-A)
***KEYWORDS  ERROR, XERMSG
***AUTHOR  Jones, R. E., (SNLA)
***DESCRIPTION

        ***Note*** Machine Dependent Routine
        FDUMP is intended to be replaced by a locally written
        version which produces a symbolic dump.  Failing this,
        it should be replaced by a version which prints the
        subprogram nesting list.  Note that this dump must be
        printed on each of up to five files, as indicated by the
        XGETUA routine.  See XSETUA and XGETUA for details.

     Written by Ron Jones, with SLATEC Common Math Library Subcommittee

***REFERENCES  (NONE)
***ROUTINES CALLED  (NONE)
***REVISION HISTORY  (YYMMDD)
   790801  DATE WRITTEN
   861211  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)

◆ I1MACH()

integer function utils::I1MACH (   I)
***PURPOSE  Return integer machine dependent constants.
***LIBRARY   SLATEC
***CATEGORY  R1
***TYPE      INTEGER (I1MACH-I)
***KEYWORDS  MACHINE CONSTANTS
***AUTHOR  Fox, P. A., (Bell Labs)
           Hall, A. D., (Bell Labs)
           Schryer, N. L., (Bell Labs)
***DESCRIPTION

   I1MACH can be used to obtain machine-dependent parameters for the
   local machine environment.  It is a function subprogram with one
   (input) argument and can be referenced as follows:

        K = I1MACH(I)

   where I=1,...,16.  The (output) value of K above is determined by
   the (input) value of I.  The results for various values of I are
   discussed below.

   I/O unit numbers:
     I1MACH( 1) = the standard input unit.
     I1MACH( 2) = the standard output unit.
     I1MACH( 3) = the standard punch unit.
     I1MACH( 4) = the standard error message unit.

   Words:
     I1MACH( 5) = the number of bits per integer storage unit.
     I1MACH( 6) = the number of characters per integer storage unit.

   Integers:
     assume integers are represented in the S-digit, base-A form

                sign ( X(S-1)*A**(S-1) + ... + X(1)*A + X(0) )

                where 0 .LE. X(I) .LT. A for I=0,...,S-1.
     I1MACH( 7) = A, the base.
     I1MACH( 8) = S, the number of base-A digits.
     I1MACH( 9) = A**S - 1, the largest magnitude.

   Floating-Point Numbers:
     Assume floating-point numbers are represented in the T-digit,
     base-B form
                sign (B**E)*( (X(1)/B) + ... + (X(T)/B**T) )

                where 0 .LE. X(I) .LT. B for I=1,...,T,
                0 .LT. X(1), and EMIN .LE. E .LE. EMAX.
     I1MACH(10) = B, the base.

   Single-Precision:
     I1MACH(11) = T, the number of base-B digits.
     I1MACH(12) = EMIN, the smallest exponent E.
     I1MACH(13) = EMAX, the largest exponent E.

   Double-Precision:
     I1MACH(14) = T, the number of base-B digits.
     I1MACH(15) = EMIN, the smallest exponent E.
     I1MACH(16) = EMAX, the largest exponent E.

   To alter this function for a particular environment, the desired
   set of DATA statements should be activated by removing the C from
   column 1.  Also, the values of I1MACH(1) - I1MACH(4) should be
   checked for consistency with the local operating system.

***REFERENCES  P. A. Fox, A. D. Hall and N. L. Schryer, Framework for
                 a portable library, ACM Transactions on Mathematical
                 Software 4, 2 (June 1978), pp. 177-188.
***ROUTINES CALLED  (NONE)
***REVISION HISTORY  (YYMMDD)
   750101  DATE WRITTEN
   891012  Added VAX G-floating constants.  (WRB)
   891012  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)
   900618  Added DEC RISC constants.  (WRB)
   900723  Added IBM RS 6000 constants.  (WRB)
   901009  Correct I1MACH(7) for IBM Mainframes. Should be 2 not 16.
           (RWC)
   910710  Added HP 730 constants.  (SMR)
   911114  Added Convex IEEE constants.  (WRB)
   920121  Added SUN -r8 compiler option constants.  (WRB)
   920229  Added Touchstone Delta i860 constants.  (WRB)
   920501  Reformatted the REFERENCES section.  (WRB)
   920625  Added Convex -p8 and -pd8 compiler option constants.
           (BKS, WRB)
   930201  Added DEC Alpha and SGI constants.  (RWC and WRB)
   930618  Corrected I1MACH(5) for Convex -p8 and -pd8 compiler
           options.  (DWL, RWC and WRB).

◆ J4SAVE()

function utils::J4SAVE (   IWHICH,
  IVALUE,
logical  ISET 
)
***SUBSIDIARY
***PURPOSE  Save or recall global variables needed by error
            handling routines.
***LIBRARY   SLATEC (XERROR)
***TYPE      INTEGER (J4SAVE-I)
***KEYWORDS  ERROR MESSAGES, ERROR NUMBER, RECALL, SAVE, XERROR
***AUTHOR  Jones, R. E., (SNLA)
***DESCRIPTION

     Abstract
        J4SAVE saves and recalls several global variables needed
        by the library error handling routines.

     Description of Parameters
      --Input--
        IWHICH - Index of item desired.
                = 1 Refers to current error number.
                = 2 Refers to current error control flag.
                = 3 Refers to current unit number to which error
                    messages are to be sent.  (0 means use standard.)
                = 4 Refers to the maximum number of times any
                     message is to be printed (as set by XERMAX).
                = 5 Refers to the total number of units to which
                     each error message is to be written.
                = 6 Refers to the 2nd unit for error messages
                = 7 Refers to the 3rd unit for error messages
                = 8 Refers to the 4th unit for error messages
                = 9 Refers to the 5th unit for error messages
        IVALUE - The value to be set for the IWHICH-th parameter,
                 if ISET is .TRUE. .
        ISET   - If ISET=.TRUE., the IWHICH-th parameter will BE
                 given the value, IVALUE.  If ISET=.FALSE., the
                 IWHICH-th parameter will be unchanged, and IVALUE
                 is a dummy parameter.
      --Output--
        The (old) value of the IWHICH-th parameter will be returned
        in the function value, J4SAVE.

***SEE ALSO  XERMSG
***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
                 Error-handling Package, SAND82-0800, Sandia
                 Laboratories, 1982.
***ROUTINES CALLED  (NONE)
***REVISION HISTORY  (YYMMDD)
   790801  DATE WRITTEN
   891214  Prologue converted to Version 4.0 format.  (BAB)
   900205  Minor modifications to prologue.  (WRB)
   900402  Added TYPE section.  (WRB)
   910411  Added KEYWORDS section.  (WRB)
   920501  Reformatted the REFERENCES section.  (WRB)

◆ Q1MACH()

real(kind=ep1) function utils::Q1MACH ( integer  I)
***PURPOSE  Return floating point machine dependent constants.
***LIBRARY   SLATEC
***CATEGORY  R1
***TYPE      DOUBLE PRECISION (R1MACH-S, Q1MACH-D)
***KEYWORDS  MACHINE CONSTANTS
***AUTHOR  Fox, P. A., (Bell Labs)
           Hall, A. D., (Bell Labs)
           Schryer, N. L., (Bell Labs)
***DESCRIPTION

   Q1MACH can be used to obtain machine-dependent parameters for the
   local machine environment.  It is a function subprogram with one
   (input) argument, and can be referenced as follows:

        D = Q1MACH(I)

   where I=1,...,5.  The (output) value of D above is determined by
   the (input) value of I.  The results for various values of I are
   discussed below.

   Q1MACH( 1) = B**(EMIN-1), the smallest positive magnitude.
   Q1MACH( 2) = B**EMAX*(1 - B**(-T)), the largest magnitude.
   Q1MACH( 3) = B**(-T), the smallest relative spacing.
   Q1MACH( 4) = B**(1-T), the largest relative spacing.
   Q1MACH( 5) = LOG10(B)

   Assume double precision numbers are represented in the T-digit,
   base-B form

              sign (B**E)*( (X(1)/B) + ... + (X(T)/B**T) )

   where 0 .LE. X(I) .LT. B for I=1,...,T, 0 .LT. X(1), and
   EMIN .LE. E .LE. EMAX.

   The values of B, T, EMIN and EMAX are provided in I1MACH as
   follows:
   I1MACH(10) = B, the base.
   I1MACH(14) = T, the number of base-B digits.
   I1MACH(15) = EMIN, the smallest exponent E.
   I1MACH(16) = EMAX, the largest exponent E.

   To alter this function for a particular environment, the desired
   set of DATA statements should be activated by removing the C from
   column 1.  Also, the values of Q1MACH(1) - Q1MACH(4) should be
   checked for consistency with the local operating system.

***REFERENCES  P. A. Fox, A. D. Hall and N. L. Schryer, Framework for
                 a portable library, ACM Transactions on Mathematical
                 Software 4, 2 (June 1978), pp. 177-188.
***ROUTINES CALLED  XERMSG
***REVISION HISTORY  (YYMMDD)
   750101  DATE WRITTEN
   890213  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)
   900315  CALLs to XERROR changed to CALLs to XERMSG.  (THJ)
   900618  Added DEC RISC constants.  (WRB)
   900723  Added IBM RS 6000 constants.  (WRB)
   900911  Added SUN 386i constants.  (WRB)
   910710  Added HP 730 constants.  (SMR)
   911114  Added Convex IEEE constants.  (WRB)
   920121  Added SUN -r8 compiler option constants.  (WRB)
   920229  Added Touchstone Delta i860 constants.  (WRB)
   920501  Reformatted the REFERENCES section.  (WRB)
   920625  Added CONVEX -p8 and -pd8 compiler option constants.
           (BKS, WRB)
   930201  Added DEC Alpha and SGI constants.  (RWC and WRB)
   121204  Hard-coded constants replaced by FORTRAN intrinsic functions (Z.Masin)

◆ R1MACH()

function utils::R1MACH (   I)
***PURPOSE  Return floating point machine dependent constants.
***LIBRARY   SLATEC
***CATEGORY  R1
***TYPE      SINGLE PRECISION (R1MACH-S, D1MACH-D)
***KEYWORDS  MACHINE CONSTANTS
***AUTHOR  Fox, P. A., (Bell Labs)
           Hall, A. D., (Bell Labs)
           Schryer, N. L., (Bell Labs)
***DESCRIPTION

   R1MACH can be used to obtain machine-dependent parameters for the
   local machine environment.  It is a function subprogram with one
   (input) argument, and can be referenced as follows:

        A = R1MACH(I)

   where I=1,...,5.  The (output) value of A above is determined by
   the (input) value of I.  The results for various values of I are
   discussed below.

   R1MACH(1) = B**(EMIN-1), the smallest positive magnitude.
   R1MACH(2) = B**EMAX*(1 - B**(-T)), the largest magnitude.
   R1MACH(3) = B**(-T), the smallest relative spacing.
   R1MACH(4) = B**(1-T), the largest relative spacing.
   R1MACH(5) = LOG10(B)

   Assume single precision numbers are represented in the T-digit,
   base-B form

              sign (B**E)*( (X(1)/B) + ... + (X(T)/B**T) )

   where 0 .LE. X(I) .LT. B for I=1,...,T, 0 .LT. X(1), and
   EMIN .LE. E .LE. EMAX.

   The values of B, T, EMIN and EMAX are provided in I1MACH as
   follows:
   I1MACH(10) = B, the base.
   I1MACH(11) = T, the number of base-B digits.
   I1MACH(12) = EMIN, the smallest exponent E.
   I1MACH(13) = EMAX, the largest exponent E.

   To alter this function for a particular environment, the desired
   set of DATA statements should be activated by removing the C from
   column 1.  Also, the values of R1MACH(1) - R1MACH(4) should be
   checked for consistency with the local operating system.

***REFERENCES  P. A. Fox, A. D. Hall and N. L. Schryer, Framework for
                 a portable library, ACM Transactions on Mathematical
                 Software 4, 2 (June 1978), pp. 177-188.
***ROUTINES CALLED  XERMSG
***REVISION HISTORY  (YYMMDD)
   790101  DATE WRITTEN
   890213  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)
   900315  CALLs to XERROR changed to CALLs to XERMSG.  (THJ)
   900618  Added DEC RISC constants.  (WRB)
   900723  Added IBM RS 6000 constants.  (WRB)
   910710  Added HP 730 constants.  (SMR)
   911114  Added Convex IEEE constants.  (WRB)
   920121  Added SUN -r8 compiler option constants.  (WRB)
   920229  Added Touchstone Delta i860 constants.  (WRB)
   920501  Reformatted the REFERENCES section.  (WRB)
   920625  Added CONVEX -p8 and -pd8 compiler option constants.
           (BKS, WRB)
   930201  Added DEC Alpha and SGI constants.  (RWC and WRB)
   121204  Hard-coded constants replaced by FORTRAN intrinsic functions (Z.Masin)

◆ search_string()

logical function utils::search_string ( integer, intent(in)  unit_no,
character(*), intent(in)  string,
logical, intent(in)  rew,
logical, intent(in), optional  fmted 
)

This function searches an input unit for the given string and returns the logical value .true. if the string has been found. In that case the input unit is positioned one line after the sought string. If the string is not found then the returned value is .false. and the input unit is positioned at its end.

Parameters
[in]unit_nounit_no Integer value corresponding to the unit to be searched.
[in]stringA string which is to be searched for on the input unit.
[in]rewLogical value. If set to .true. then the input unit is rewound before the search is commenced.
[in]fmtedOptional logical input variable. If present and set to .false. then the reading will be done using unformatted read. The default is that the input unit is open for formatted reading.
Todo:
Add a test if the input unit is open for formatted reading.
Todo:
Add a test for unformatted unit which should search for a string not present on the file. I encountered a case in which err > 0 was returned rather than err < 0 (end of file reached).

◆ XERCLR()

subroutine utils::XERCLR

*DECK XERCLR ***BEGIN PROLOGUE XERCLR ***PURPOSE Reset current error number to zero. ***LIBRARY SLATEC (XERROR) ***CATEGORY R3C ***TYPE ALL (XERCLR-A) ***KEYWORDS ERROR, XERROR ***AUTHOR Jones, R. E., (SNLA) ***DESCRIPTION

 Abstract
    This routine simply resets the current error number to zero.
    This may be necessary in order to determine that a certain
    error has occurred again since the last time NUMXER was
    referenced.

***REFERENCES R. E. Jones and D. K. Kahaner, XERROR, the SLATEC Error-handling Package, SAND82-0800, Sandia Laboratories, 1982. ***ROUTINES CALLED J4SAVE ***REVISION HISTORY (YYMMDD) 790801 DATE WRITTEN 861211 REVISION DATE from Version 3.2 891214 Prologue converted to Version 4.0 format. (BAB) 920501 Reformatted the REFERENCES section. (WRB) ***END PROLOGUE XERCLR

◆ XERCNT()

subroutine utils::XERCNT ( character*(*)  LIBRAR,
character*(*)  SUBROU,
character*(*)  MESSG,
  NERR,
  LEVEL,
  KONTRL 
)
***SUBSIDIARY
***PURPOSE  Allow user control over handling of errors.
***LIBRARY   SLATEC (XERROR)
***CATEGORY  R3C
***TYPE      ALL (XERCNT-A)
***KEYWORDS  ERROR, XERROR
***AUTHOR  Jones, R. E., (SNLA)
***DESCRIPTION

     Abstract
        Allows user control over handling of individual errors.
        Just after each message is recorded, but before it is
        processed any further (i.e., before it is printed or
        a decision to abort is made), a call is made to XERCNT.
        If the user has provided his own version of XERCNT, he
        can then override the value of KONTROL used in processing
        this message by redefining its value.
        KONTRL may be set to any value from -2 to 2.
        The meanings for KONTRL are the same as in XSETF, except
        that the value of KONTRL changes only for this message.
        If KONTRL is set to a value outside the range from -2 to 2,
        it will be moved back into that range.

     Description of Parameters

      --Input--
        LIBRAR - the library that the routine is in.
        SUBROU - the subroutine that XERMSG is being called from
        MESSG  - the first 20 characters of the error message.
        NERR   - same as in the call to XERMSG.
        LEVEL  - same as in the call to XERMSG.
        KONTRL - the current value of the control flag as set
                 by a call to XSETF.

      --Output--
        KONTRL - the new value of KONTRL.  If KONTRL is not
                 defined, it will remain at its original value.
                 This changed value of control affects only
                 the current occurrence of the current message.

***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
                 Error-handling Package, SAND82-0800, Sandia
                 Laboratories, 1982.
***ROUTINES CALLED  (NONE)
***REVISION HISTORY  (YYMMDD)
   790801  DATE WRITTEN
   861211  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)
   900206  Routine changed from user-callable to subsidiary.  (WRB)
   900510  Changed calling sequence to include LIBRARY and SUBROUTINE
           names, changed routine name from XERCTL to XERCNT.  (RWC)
   920501  Reformatted the REFERENCES section.  (WRB)

◆ XERHLT()

subroutine utils::XERHLT ( character*(*)  MESSG)
***SUBSIDIARY
***PURPOSE  Abort program execution and print error message.
***LIBRARY   SLATEC (XERROR)
***CATEGORY  R3C
***TYPE      ALL (XERHLT-A)
***KEYWORDS  ABORT PROGRAM EXECUTION, ERROR, XERROR
***AUTHOR  Jones, R. E., (SNLA)
***DESCRIPTION

     Abstract
        ***Note*** machine dependent routine
        XERHLT aborts the execution of the program.
        The error message causing the abort is given in the calling
        sequence, in case one needs it for printing on a dayfile,
        for example.

     Description of Parameters
        MESSG is as in XERMSG.

***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
                 Error-handling Package, SAND82-0800, Sandia
                 Laboratories, 1982.
***ROUTINES CALLED  (NONE)
***REVISION HISTORY  (YYMMDD)
   790801  DATE WRITTEN
   861211  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)
   900206  Routine changed from user-callable to subsidiary.  (WRB)
   900510  Changed calling sequence to delete length of character
           and changed routine name from XERABT to XERHLT.  (RWC)
   920501  Reformatted the REFERENCES section.  (WRB)

◆ XERMSG()

subroutine utils::XERMSG ( character*(*)  LIBRAR,
character*(*)  SUBROU,
character*(*)  MESSG,
  NERR,
  LEVEL 
)
***PURPOSE  Process error messages for SLATEC and other libraries.
***LIBRARY   SLATEC (XERROR)
***CATEGORY  R3C
***TYPE      ALL (XERMSG-A)
***KEYWORDS  ERROR MESSAGE, XERROR
***AUTHOR  Fong, Kirby, (NMFECC at LLNL)
***DESCRIPTION

   XERMSG processes a diagnostic message in a manner determined by the
   value of LEVEL and the current value of the library error control
   flag, KONTRL.  See subroutine XSETF for details.

    LIBRAR   A character constant (or character variable) with the name
             of the library.  This will be 'SLATEC' for the SLATEC
             Common Math Library.  The error handling package is
             general enough to be used by many libraries
             simultaneously, so it is desirable for the routine that
             detects and reports an error to identify the library name
             as well as the routine name.

    SUBROU   A character constant (or character variable) with the name
             of the routine that detected the error.  Usually it is the
             name of the routine that is calling XERMSG.  There are
             some instances where a user callable library routine calls
             lower level subsidiary routines where the error is
             detected.  In such cases it may be more informative to
             supply the name of the routine the user called rather than
             the name of the subsidiary routine that detected the
             error.

    MESSG    A character constant (or character variable) with the text
             of the error or warning message.  In the example below,
             the message is a character constant that contains a
             generic message.

                   CALL XERMSG ('SLATEC', 'MMPY',
                  *'THE ORDER OF THE MATRIX EXCEEDS THE ROW DIMENSION',
                  *3, 1)

             It is possible (and is sometimes desirable) to generate a
             specific message--e.g., one that contains actual numeric
             values.  Specific numeric values can be converted into
             character strings using formatted WRITE statements into
             character variables.  This is called standard Fortran
             internal file I/O and is exemplified in the first three
             lines of the following example.  You can also catenate
             substrings of characters to construct the error message.
             Here is an example showing the use of both writing to
             an internal file and catenating character strings.

                   CHARACTER*5 CHARN, CHARL
                   WRITE (CHARN,10) N
                   WRITE (CHARL,10) LDA
                10 FORMAT(I5)
                   CALL XERMSG ('SLATEC', 'MMPY', 'THE ORDER'//CHARN//
                  *   ' OF THE MATRIX EXCEEDS ITS ROW DIMENSION OF'//
                  *   CHARL, 3, 1)

             There are two subtleties worth mentioning.  One is that
             the // for character catenation is used to construct the
             error message so that no single character constant is
             continued to the next line.  This avoids confusion as to
             whether there are trailing blanks at the end of the line.
             The second is that by catenating the parts of the message
             as an actual argument rather than encoding the entire
             message into one large character variable, we avoid
             having to know how long the message will be in order to
             declare an adequate length for that large character
             variable.  XERMSG calls XERPRN to print the message using
             multiple lines if necessary.  If the message is very long,
             XERPRN will break it into pieces of 72 characters (as
             requested by XERMSG) for printing on multiple lines.
             Also, XERMSG asks XERPRN to prefix each line with ' *  '
             so that the total line length could be 76 characters.
             Note also that XERPRN scans the error message backwards
             to ignore trailing blanks.  Another feature is that
             the substring '$$' is treated as a new line sentinel
             by XERPRN.  If you want to construct a multiline
             message without having to count out multiples of 72
             characters, just use '$$' as a separator.  '$$'
             obviously must occur within 72 characters of the
             start of each line to have its intended effect since
             XERPRN is asked to wrap around at 72 characters in
             addition to looking for '$$'.

    NERR     An integer value that is chosen by the library routine's
             author.  It must be in the range -99 to 999 (three
             printable digits).  Each distinct error should have its
             own error number.  These error numbers should be described
             in the machine readable documentation for the routine.
             The error numbers need be unique only within each routine,
             so it is reasonable for each routine to start enumerating
             errors from 1 and proceeding to the next integer.

    LEVEL    An integer value in the range 0 to 2 that indicates the
             level (severity) of the error.  Their meanings are

            -1  A warning message.  This is used if it is not clear
                that there really is an error, but the user's attention
                may be needed.  An attempt is made to only print this
                message once.

             0  A warning message.  This is used if it is not clear
                that there really is an error, but the user's attention
                may be needed.

             1  A recoverable error.  This is used even if the error is
                so serious that the routine cannot return any useful
                answer.  If the user has told the error package to
                return after recoverable errors, then XERMSG will
                return to the Library routine which can then return to
                the user's routine.  The user may also permit the error
                package to terminate the program upon encountering a
                recoverable error.

             2  A fatal error.  XERMSG will not return to its caller
                after it receives a fatal error.  This level should
                hardly ever be used; it is much better to allow the
                user a chance to recover.  An example of one of the few
                cases in which it is permissible to declare a level 2
                error is a reverse communication Library routine that
                is likely to be called repeatedly until it integrates
                across some interval.  If there is a serious error in
                the input such that another step cannot be taken and
                the Library routine is called again without the input
                error having been corrected by the caller, the Library
                routine will probably be called forever with improper
                input.  In this case, it is reasonable to declare the
                error to be fatal.

    Each of the arguments to XERMSG is input; none will be modified by
    XERMSG.  A routine may make multiple calls to XERMSG with warning
    level messages; however, after a call to XERMSG with a recoverable
    error, the routine should return to the user.  Do not try to call
    XERMSG with a second recoverable error after the first recoverable
    error because the error package saves the error number.  The user
    can retrieve this error number by calling another entry point in
    the error handling package and then clear the error number when
    recovering from the error.  Calling XERMSG in succession causes the
    old error number to be overwritten by the latest error number.
    This is considered harmless for error numbers associated with
    warning messages but must not be done for error numbers of serious
    errors.  After a call to XERMSG with a recoverable error, the user
    must be given a chance to call NUMXER or XERCLR to retrieve or
    clear the error number.
***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
                 Error-handling Package, SAND82-0800, Sandia
                 Laboratories, 1982.
***ROUTINES CALLED  FDUMP, J4SAVE, XERCNT, XERHLT, XERPRN, XERSVE
***REVISION HISTORY  (YYMMDD)
   880101  DATE WRITTEN
   880621  REVISED AS DIRECTED AT SLATEC CML MEETING OF FEBRUARY 1988.
           THERE ARE TWO BASIC CHANGES.
           1.  A NEW ROUTINE, XERPRN, IS USED INSTEAD OF XERPRT TO
               PRINT MESSAGES.  THIS ROUTINE WILL BREAK LONG MESSAGES
               INTO PIECES FOR PRINTING ON MULTIPLE LINES.  '$$' IS
               ACCEPTED AS A NEW LINE SENTINEL.  A PREFIX CAN BE
               ADDED TO EACH LINE TO BE PRINTED.  XERMSG USES EITHER
               ' ***' OR ' *  ' AND LONG MESSAGES ARE BROKEN EVERY
               72 CHARACTERS (AT MOST) SO THAT THE MAXIMUM LINE
               LENGTH OUTPUT CAN NOW BE AS GREAT AS 76.
           2.  THE TEXT OF ALL MESSAGES IS NOW IN UPPER CASE SINCE THE
               FORTRAN STANDARD DOCUMENT DOES NOT ADMIT THE EXISTENCE
               OF LOWER CASE.
   880708  REVISED AFTER THE SLATEC CML MEETING OF JUNE 29 AND 30.
           THE PRINCIPAL CHANGES ARE
           1.  CLARIFY COMMENTS IN THE PROLOGUES
           2.  RENAME XRPRNT TO XERPRN
           3.  REWORK HANDLING OF '$$' IN XERPRN TO HANDLE BLANK LINES
               SIMILAR TO THE WAY FORMAT STATEMENTS HANDLE THE /
               CHARACTER FOR NEW RECORDS.
   890706  REVISED WITH THE HELP OF FRED FRITSCH AND REG CLEMENS TO
           CLEAN UP THE CODING.
   890721  REVISED TO USE NEW FEATURE IN XERPRN TO COUNT CHARACTERS IN
           PREFIX.
   891013  REVISED TO CORRECT COMMENTS.
   891214  Prologue converted to Version 4.0 format.  (WRB)
   900510  Changed test on NERR to be -9999999 < NERR < 99999999, but
           NERR .ne. 0, and on LEVEL to be -2 < LEVEL < 3.  Added
           LEVEL=-1 logic, changed calls to XERSAV to XERSVE, and
           XERCTL to XERCNT.  (RWC)
   920501  Reformatted the REFERENCES section.  (WRB)

◆ XERPRN()

subroutine utils::XERPRN ( character*(*)  PREFIX,
integer  NPREF,
character*(*)  MESSG,
integer  NWRAP 
)
***SUBSIDIARY
***PURPOSE  Print error messages processed by XERMSG.
***LIBRARY   SLATEC (XERROR)
***CATEGORY  R3C
***TYPE      ALL (XERPRN-A)
***KEYWORDS  ERROR MESSAGES, PRINTING, XERROR
***AUTHOR  Fong, Kirby, (NMFECC at LLNL)
***DESCRIPTION

 This routine sends one or more lines to each of the (up to five)
 logical units to which error messages are to be sent.  This routine
 is called several times by XERMSG, sometimes with a single line to
 print and sometimes with a (potentially very long) message that may
 wrap around into multiple lines.

 PREFIX  Input argument of type CHARACTER.  This argument contains
         characters to be put at the beginning of each line before
         the body of the message.  No more than 16 characters of
         PREFIX will be used.

 NPREF   Input argument of type INTEGER.  This argument is the number
         of characters to use from PREFIX.  If it is negative, the
         intrinsic function LEN is used to determine its length.  If
         it is zero, PREFIX is not used.  If it exceeds 16 or if
         LEN(PREFIX) exceeds 16, only the first 16 characters will be
         used.  If NPREF is positive and the length of PREFIX is less
         than NPREF, a copy of PREFIX extended with blanks to length
         NPREF will be used.

 MESSG   Input argument of type CHARACTER.  This is the text of a
         message to be printed.  If it is a long message, it will be
         broken into pieces for printing on multiple lines.  Each line
         will start with the appropriate prefix and be followed by a
         piece of the message.  NWRAP is the number of characters per
         piece; that is, after each NWRAP characters, we break and
         start a new line.  In addition the characters '$$' embedded
         in MESSG are a sentinel for a new line.  The counting of
         characters up to NWRAP starts over for each new line.  The
         value of NWRAP typically used by XERMSG is 72 since many
         older error messages in the SLATEC Library are laid out to
         rely on wrap-around every 72 characters.

 NWRAP   Input argument of type INTEGER.  This gives the maximum size
         piece into which to break MESSG for printing on multiple
         lines.  An embedded '$$' ends a line, and the count restarts
         at the following character.  If a line break does not occur
         on a blank (it would split a word) that word is moved to the
         next line.  Values of NWRAP less than 16 will be treated as
         16.  Values of NWRAP greater than 132 will be treated as 132.
         The actual line length will be NPREF + NWRAP after NPREF has
         been adjusted to fall between 0 and 16 and NWRAP has been
         adjusted to fall between 16 and 132.

***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
                 Error-handling Package, SAND82-0800, Sandia
                 Laboratories, 1982.
***ROUTINES CALLED  I1MACH, XGETUA
***REVISION HISTORY  (YYMMDD)
   880621  DATE WRITTEN
   880708  REVISED AFTER THE SLATEC CML SUBCOMMITTEE MEETING OF
           JUNE 29 AND 30 TO CHANGE THE NAME TO XERPRN AND TO REWORK
           THE HANDLING OF THE NEW LINE SENTINEL TO BEHAVE LIKE THE
           SLASH CHARACTER IN FORMAT STATEMENTS.
   890706  REVISED WITH THE HELP OF FRED FRITSCH AND REG CLEMENS TO
           STREAMLINE THE CODING AND FIX A BUG THAT CAUSED EXTRA BLANK
           LINES TO BE PRINTED.
   890721  REVISED TO ADD A NEW FEATURE.  A NEGATIVE VALUE OF NPREF
           CAUSES LEN(PREFIX) TO BE USED AS THE LENGTH.
   891013  REVISED TO CORRECT ERROR IN CALCULATING PREFIX LENGTH.
   891214  Prologue converted to Version 4.0 format.  (WRB)
   900510  Added code to break messages between words.  (RWC)
   920501  Reformatted the REFERENCES section.  (WRB)

◆ XERSVE()

subroutine utils::XERSVE ( character*(*)  LIBRAR,
character*(*)  SUBROU,
character*(*)  MESSG,
  KFLAG,
  NERR,
  LEVEL,
  ICOUNT 
)
***SUBSIDIARY
***PURPOSE  Record that an error has occurred.
***LIBRARY   SLATEC (XERROR)
***CATEGORY  R3
***TYPE      ALL (XERSVE-A)
***KEYWORDS  ERROR, XERROR
***AUTHOR  Jones, R. E., (SNLA)
***DESCRIPTION

 *Usage:

        INTEGER  KFLAG, NERR, LEVEL, ICOUNT
        CHARACTER * (len) LIBRAR, SUBROU, MESSG

        CALL XERSVE (LIBRAR, SUBROU, MESSG, KFLAG, NERR, LEVEL, ICOUNT)

 *Arguments:

        LIBRAR :IN    is the library that the message is from.
        SUBROU :IN    is the subroutine that the message is from.
        MESSG  :IN    is the message to be saved.
        KFLAG  :IN    indicates the action to be performed.
                      when KFLAG > 0, the message in MESSG is saved.
                      when KFLAG=0 the tables will be dumped and
                      cleared.
                      when KFLAG < 0, the tables will be dumped and
                      not cleared.
        NERR   :IN    is the error number.
        LEVEL  :IN    is the error severity.
        ICOUNT :OUT   the number of times this message has been seen,
                      or zero if the table has overflowed and does not
                      contain this message specifically.  When KFLAG=0,
                      ICOUNT will not be altered.

 *Description:

   Record that this error occurred and possibly dump and clear the
   tables.

***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
                 Error-handling Package, SAND82-0800, Sandia
                 Laboratories, 1982.
***ROUTINES CALLED  I1MACH, XGETUA
***REVISION HISTORY  (YYMMDD)
   800319  DATE WRITTEN
   861211  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)
   900413  Routine modified to remove reference to KFLAG.  (WRB)
   900510  Changed to add LIBRARY NAME and SUBROUTINE to calling
           sequence, use IF-THEN-ELSE, make number of saved entries
           easily changeable, changed routine name from XERSAV to
           XERSVE.  (RWC)
   910626  Added LIBTAB and SUBTAB to SAVE statement.  (BKS)
   920501  Reformatted the REFERENCES section.  (WRB)

◆ XGETUA()

subroutine utils::XGETUA ( dimension(5)  IUNITA,
  N 
)
***PURPOSE  Return unit number(s) to which error messages are being
            sent.
***LIBRARY   SLATEC (XERROR)
***CATEGORY  R3C
***TYPE      ALL (XGETUA-A)
***KEYWORDS  ERROR, XERROR
***AUTHOR  Jones, R. E., (SNLA)
***DESCRIPTION

     Abstract
        XGETUA may be called to determine the unit number or numbers
        to which error messages are being sent.
        These unit numbers may have been set by a call to XSETUN,
        or a call to XSETUA, or may be a default value.

     Description of Parameters
      --Output--
        IUNIT - an array of one to five unit numbers, depending
                on the value of N.  A value of zero refers to the
                default unit, as defined by the I1MACH machine
                constant routine.  Only IUNIT(1),...,IUNIT(N) are
                defined by XGETUA.  The values of IUNIT(N+1),...,
                IUNIT(5) are not defined (for N .LT. 5) or altered
                in any way by XGETUA.
        N     - the number of units to which copies of the
                error messages are being sent.  N will be in the
                range from 1 to 5.

***REFERENCES  R. E. Jones and D. K. Kahaner, XERROR, the SLATEC
                 Error-handling Package, SAND82-0800, Sandia
                 Laboratories, 1982.
***ROUTINES CALLED  J4SAVE
***REVISION HISTORY  (YYMMDD)
   790801  DATE WRITTEN
   861211  REVISION DATE from Version 3.2
   891214  Prologue converted to Version 4.0 format.  (BAB)
   920501  Reformatted the REFERENCES section.  (WRB)