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
eqstr

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

     EQSTR ( Equivalent strings )

     LOGICAL FUNCTION EQSTR ( A, B )

Abstract

     Determine whether two strings are equivalent.

Required_Reading

     None.

Keywords

     ALPHANUMERIC
     ASCII
     CHARACTER
     COMPARE
     PARSING
     SEARCH
     STRING
     TEXT

Declarations

     IMPLICIT NONE

     CHARACTER*(*)         A
     CHARACTER*(*)         B

Brief_I/O

     VARIABLE  I/O  DESCRIPTION
     --------  ---  --------------------------------------------------
     A,
     B          I   Arbitrary character strings.

     The function returns .TRUE. if A and B are equivalent.

Detailed_Input

     A,
     B        are arbitrary character strings.

Detailed_Output

     The function returns .TRUE. if A and B are equivalent: that is,
     if A and B contain  the same characters in the same order,
     when blanks are ignored and uppercase and lowercase characters
     are considered equal.

Parameters

     None.

Exceptions

     Error free.

Files

     None.

Particulars

     This routine is provided for those cases in which two strings
     must be compared, and in which allowances are to be made for
     extra (leading, trailing, and embedded) blanks and differences
     in case. For the most part,

        EQSTR ( A, B )

     is .TRUE. whenever

        CALL CMPRSS ( ' ', 0, A, TEMPA )
        CALL UCASE  (            TEMPA, TEMPA )

        CALL CMPRSS ( ' ', 0, B, TEMPB )
        CALL UCASE  (            TEMPB, TEMPB )

        EQVLNT = TEMPA .EQ. TEMPB

     is .TRUE. There are two important differences, however.

        1) The single reference to EQSTR is much simpler to
           write, and simpler to understand.

        2) The reference to EQSTR does not require any temporary
           storage, nor does it require that the strings A and B
           be changed. This feature is especially useful when
           comparing strings received as subprogram arguments
           against strings stored internally within the subprogram.

Examples

     The numerical results shown for this example may differ across
     platforms. The results depend on the SPICE kernels used as
     input, the compiler and supporting libraries, and the machine
     specific arithmetic implementation.

     1) This code provides examples of equivalent and non-equivalent
        strings according to the algorithm implemented in EQSTR.

        Example code begins here.


              PROGRAM EQSTR_EX1
              IMPLICIT NONE

        C
        C     SPICELIB functions.
        C
              LOGICAL               EQSTR

        C
        C     Local parameters.
        C
              INTEGER               SETSIZ
              PARAMETER           ( SETSIZ = 9  )

              INTEGER               STRLEN
              PARAMETER           ( STRLEN = 22 )

        C
        C     Local variables.
        C
              CHARACTER*(STRLEN)    STR1   ( SETSIZ )
              CHARACTER*(STRLEN)    STR2   ( SETSIZ )

              INTEGER               I

        C
        C     Initialize the two arrays of strings.
        C
              DATA                  STR1   / 'A short string   ',
             .                               'Embedded        blanks',
             .                               'Embedded        blanks',
             .                               ' ',
             .                               'One word left out',
             .                               'Extra [] delimiters',
             .                               'Testing 1, 2, 3',
             .                               'Case insensitive',
             .                               'Steve'  /

              DATA                  STR2   / 'ashortstring',
             .                               'Em be dd ed bl an ks',
             .                               '   Embeddedblanks',
             .                               '          ',
             .                               'WORD LEFT OUT',
             .                               'extradelimiters',
             .                               'TESTING123',
             .                               'Case Insensitive',
             .                               '  S t E v E  '  /


        C
        C     Compare the two arrays.
        C
              DO I = 1, SETSIZ

                 WRITE(*,*)
                 WRITE(*,*) 'STR1 : ', STR1(I)
                 WRITE(*,*) 'STR2 : ', STR2(I)

                 IF ( EQSTR( STR1(I), STR2(I) ) ) THEN

                    WRITE(*,*) 'EQSTR: equivalent.'

                 ELSE

                    WRITE(*,*) 'EQSTR: NOT equivalent.'

                 END IF

              END DO

              END


        When this program was executed on a Mac/Intel/gfortran/64-bit
        platform, the output was:


         STR1 : A short string
         STR2 : ashortstring
         EQSTR: equivalent.

         STR1 : Embedded        blanks
         STR2 : Em be dd ed bl an ks
         EQSTR: equivalent.

         STR1 : Embedded        blanks
         STR2 :    Embeddedblanks
         EQSTR: equivalent.

         STR1 :
         STR2 :
         EQSTR: equivalent.

         STR1 : One word left out
         STR2 : WORD LEFT OUT
         EQSTR: NOT equivalent.

         STR1 : Extra [] delimiters
         STR2 : extradelimiters
         EQSTR: NOT equivalent.

         STR1 : Testing 1, 2, 3
         STR2 : TESTING123
         EQSTR: NOT equivalent.

         STR1 : Case insensitive
         STR2 : Case Insensitive
         EQSTR: equivalent.

         STR1 : Steve
         STR2 :   S t E v E
         EQSTR: equivalent.

Restrictions

     None.

Literature_References

     None.

Author_and_Institution

     N.J. Bachman       (JPL)
     J. Diaz del Rio    (ODC Space)
     W.L. Taber         (JPL)
     I.M. Underwood     (JPL)

Version

    SPICELIB Version 1.3.0, 06-JUL-2021 (JDR)

        Added IMPLICIT NONE statement.

        Edited the header to comply with NAIF standard. Added complete
        code example based on existing example fragments.

    SPICELIB Version 1.2.0, 03-AUG-1994 (NJB)

        Code changed to eliminate DO WHILE ( .TRUE. ) construct.
        The purpose of the change was to eliminate compilation
        diagnostics relating to unreachable statements. The code
        ran just fine before this change.

    SPICELIB Version 1.1.1, 10-MAR-1992 (WLT)

        Comment section for permuted index source lines was added
        following the header.

    SPICELIB Version 1.1.0, 10-MAY-1990 (NJB)

        Loop termination condition fixed.

    SPICELIB Version 1.0.0, 31-JAN-1990 (IMU)
Fri Dec 31 18:36:20 2021