6.3.2.1 Character Functions

Fortran provides four character functions: CHAR, ICHAR, INDEX, and LEN.

CHAR Function

The CHAR function converts an ASCII integer value (with a range of 0 to 255) to a character value and returns the character value. It takes the following form:

CHAR (i)
i
Is an integer expression.

ICHAR Function

The ICHAR function converts a character expression to its equivalent ASCII code and returns the ASCII value. It takes the following form:

ICHAR (c)
c
Is the character to be converted to an ASCII code. If c is longer than one byte, only the value of the first byte is returned; the remainder is ignored.

INDEX Function

The INDEX function searches for a substring (c2) in a specified character string (c1) and, if it finds the substring, returns the substring's starting position. If c2 occurs more than once in c1, the starting position of the first (leftmost) occurrence is returned. If c2 does not occur in c1, the value zero is returned. The INDEX function takes the following form:

INDEX (c1,c2)
c1
Is a character expression specifying the string to be searched for the substring specified by c2.
c2
Is a character expression specifying the substring for which the starting location is to be determined.

An example of the INDEX function follows:

      SUBROUTINE FIND_SUBSTRINGS(SUB,S)
      CHARACTER*(*) SUB, S
      CHARACTER*132 MARKS

      I = 1
      MARKS = ' '

10    J = INDEX(S(I:), SUB)
      IF (J .NE. 0) THEN
          I = I + (J-1)
          MARKS(I:I) = '#'
          I = I + 1
          IF (I .LE. LEN(S)) GO TO 10
          END IF

      WRITE (6,91) S, MARKS
91    FORMAT (2(/1X,A))
      END

LEN Function

The LEN function returns the length of a character expression. It takes the following form:

LEN (c)
c
Is a character expression. The value returned indicates how many bytes there are in the expression.

An example of the LEN function follows:

      SUBROUTINE REVERSE(S)
      CHARACTER T, S*(*)

      J = LEN(S)
      DO 10 I=1,J/2
          T = S(I:I)
          S(I:I) = S(J:J)
          S(J:J) = T
          J = J - 1
10    CONTINUE

      RETURN
      END


Previous Page Next Page Table of Contents