Index of Functions: A  B  C  D  E  F  G  H  I  J  K  L  M  N  O  P  Q  R  S  T  U  V  W  X 
Index Page
lxname

Table of contents
Procedure
Abstract
Required_Reading
Keywords
Declarations
Brief_I/O
Detailed_Input
Detailed_Output
Parameters
Exceptions
Files
Particulars
Examples
Restrictions
Literature_References
Author_and_Institution
Version

Procedure

     LXNAME ( Lex names )

     SUBROUTINE LXNAME ( HDCHRS, TLCHRS, STRING, FIRST, LAST, IDSPEC,
    .                    NCHAR                                        )

Abstract

     Umbrella routine for name scanning entry points.

Required_Reading

     None.

Keywords

     CHARACTER
     PARSING
     SCANNING
     STRING
     UTILITY

Declarations

     IMPLICIT NONE

     INTEGER               LBCELL
     PARAMETER           ( LBCELL = -5 )

     INTEGER               MXSPEC
     PARAMETER           ( MXSPEC = 512 )

     CHARACTER*(*)         HDCHRS
     CHARACTER*(*)         TLCHRS
     CHARACTER*(*)         STRING
     INTEGER               FIRST
     INTEGER               IDSPEC ( LBCELL : * )
     INTEGER               LAST
     INTEGER               NCHAR

Brief_I/O

     VARIABLE  I/O  ENTRY POINTS
     --------  ---  --------------------------------------------------
     HDCHRS     I   LXCSID
     TLCHRS     I   LXCSID
     STRING     I   LXIDNT
     FIRST      I   LXIDNT
     IDSPEC    I-O  LXDFID, LXCSID, LXIDNT
     LAST       O   LXIDNT
     NCHAR      O   LXIDNT
     MXSPEC     P   LXDFID, LXCSID
     LBCELL     P   LXIDNT, LXDFID, LXCSID

Detailed_Input

     See the entry points for descriptions of their inputs.

Detailed_Output

     See the entry points for descriptions of their outputs.

Parameters

     See the entry points for descriptions of their parameters.

Exceptions

     See the entry points for descriptions of the exceptions specific
     to those entry points.

     1)  If this routine is called directly, the error
         SPICE(BOGUSENTRY) is signaled.

Files

     None.

Particulars

     Many computer languages include tokens that represent names.
     Examples of names include procedure names and variable names.
     The term `identifier' is generally used to indicate this type
     of token. Rules for constructing identifiers vary from
     language to language, but identifiers conforming to the
     following rules are widely recognized:

        1)  The first character of the identifier is a letter.

        2)  The remaining characters are letters or numbers.

        3)  The length of the identifier is less than some specified
            limit.

     This suite of routines has its own set of default rules for
     forming identifiers. These rules are somewhat more liberal
     than those listed above. Rule (1) above still holds, but
     trailing characters may include letters, numbers, and the
     special characters

        $
        _  (underscore)

     No mechanism for enforcing rule (3) is provided; this task is
     left to the caller, since this routine would be unnecessarily
     complicated by the need to construct diagnostic messages.

     The entry point LXIDNT (Lex identifier) recognizes valid
     identifier tokens, using either the default character sets
     for the head and tail of the identifier, or character sets
     specified in the last call to LXCSID.

     In order to use this suite of routines to scan identifiers that
     conform to the default rules, a program normally calls the entry
     point LXDFID (Lex, default identifier specification) once to
     obtain the default `identifier specification'. This specification
     is an integer array in which the allowed head and tail character
     sets are specified. This specification is then saved and supplied
     to the entry point LXIDNT (Lex identifier) whenever LXIDNT is
     called to scan an identifier. The entry point LXIDNT  recognizes
     valid identifier tokens, using an input identifier specification
     to decide which head and tail characters are allowed in an
     identifier.

     The scanning code using these routines might have the following
     structure:


              INTEGER               IDSPEC ( LBCELL : MXSPEC )
                 .
                 .
                 .
        C
        C     Initialize the identifier specification, using the
        C     default:
        C
              CALL SSIZEI ( MXSPEC, IDSPEC )
              CALL LXDFID ( IDSPEC )
                 .
                 .
                 .
        C
        C     Scan string:
        C
              DO WHILE ( <more tokens> )
                       .
                       .
                       .
                 IF ( <test for identifier> ) THEN

                    CALL LXIDNT ( IDSPEC, STRING, FIRST, LAST, NCHARS )

                    IF ( NCHARS .GT. 0 ) THEN

                       [Identifier was found--process result]

                    ELSE

                       [Token at starting at location FIRST was not
                        an identifier--handle alternatives]

                    END IF

                 ELSE

                    [ perform tests for other tokens ]

                 END IF

              END DO


     It is possible to override the default rules by calling the
     entry point LXCSID (Lex, custom identifier characters).  This
     routine allows the caller to specify the precise set of
     characters allowed as the first character (`head') of the
     identifier, as well as those allowed in the remainder (`tail')
     of the identifier.

     If a custom identifier specification is desired, the call to
     LXDFID in the pseudo code above would be replaced by a call to
     LXCSID. After setting the strings HDCHRS and TLCHRS to contain,
     respectively, the allowed head and tail identifier characters, the
     following call would produce an identifier specification structure
     IDSPEC representing these set of allowed characters.

        CALL LXCSID ( HDCHRS, TLCHRS, IDSPEC )

     The array IDSPEC obtained from LXCSID would be used as input to
     LXIDNT, instead of using the array obtained by calling LXDFID.

Examples

     1)  The following table illustrates the behavior of the scanning
         entry point LXIDNT when the default identifier syntax is in
         effect:

         STRING CONTENTS             FIRST   LAST   NCHAR
         ==========================================================
         WHERE A LT B                1       5      5
         WHERE A LT B                7       7      1
         WHERE A.LT.B                7       7      1
         WHERE (A0)LT(B8)            8       9      2
         WHERE A0$LT_B7              7       14     8
         WHERE A LT B                12      12     1
         WHERE A .LT. B              9       8      0


     2)  The following table illustrates the behavior of the scanning
         entry point LXIDNT when a custom identifier syntax is used.
         The call

            CALL LXCSID ( HDCHRS, TLCHRS, IDSPEC )

         where

            HDCHRS = 'abcdefghijklmnopqrstuvwxyz'

         and

            TLCHRS = 'abcdefghijklmnopqrstuvwxyz012345.'

        will produce an identifier specification IDSPEC that,
        when supplied as an input to LXIDNT, will cause LXIDNT
        to perform in accordance with the table shown below:


         STRING CONTENTS             FIRST   LAST   NCHAR
         ==========================================================
         WHERE A LT B                1       0      0
         where a lt b                1       5      5
         WHERE a LT b                7       7      1
         WHERE a.LT.b                7       8      2
         WHERE (a0)LT(b8)            14      14     1
         WHERE (a0)LT(b5)            14      15     2
         WHERE a0.lt.b8              7       13     7
         WHERE a0$lt_b7              7       8      2
         where a .lt. b              9       12     4

Restrictions

     None.

Literature_References

     None.

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)
     B.V. Semenov       (JPL)

Version

    SPICELIB Version 1.1.0, 26-OCT-2021 (JDR)

        Added IMPLICIT NONE statement.

        Edited the header to comply with NAIF standard.

    SPICELIB Version 1.0.1, 10-FEB-2014 (BVS)

        Added LBCELL to the $Brief_I/O section.

    SPICELIB Version 1.0.0, 25-OCT-1995 (NJB)
Fri Dec 31 18:36:33 2021