Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=MaxNameLength), | intent(in) | :: | lineOfText | |||
integer, | intent(inout) | :: | endOfScan | |||
character(len=MaxNameLength), | intent(out) | :: | aWord |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE GetLastWord(lineOfText,endOfScan,aWord)
! SUBROUTINE INFORMATION:
! AUTHOR Jason Glazer of GARD Analytics, Inc.
! DATE WRITTEN June 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Returns the last substring of the line of text to the
! left of the endOfSubStrg pointer. A substring is
! delimitted by spaces. Quotes are not significant
! (they are treated just like any other non-space character)
! METHODOLOGY EMPLOYED:
! Scan the string from the end.
! REFERENCES:
! na
! USE STATEMENTS:
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
CHARACTER(len=MaxNameLength),INTENT(IN) :: lineOfText
INTEGER, INTENT(INOUT) :: endOfScan
CHARACTER(len=MaxNameLength),INTENT(OUT) :: aWord
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: iString
INTEGER :: curEndOfScan
LOGICAL :: isInWord
LOGICAL :: isSpace
INTEGER :: beginOfWord
INTEGER :: endOfWord
curEndOfScan = endOfScan
IF (curEndOfScan .GT. 0) THEN
IF (curEndOfScan .GT. LEN_TRIM(lineOfText)) THEN
curEndOfScan = LEN_TRIM(lineOfText)
END IF
!check if currently on a space or not
IF (lineOfText(curEndOfScan:curEndOfScan) .EQ. ' ') THEN
isInWord = .FALSE.
beginOfWord = 0
endOfWord = 0
ELSE
isInWord = .TRUE.
beginOfWord = curEndOfScan
endOfWord = curEndOfScan
END IF
!scan backwards from
DO iString=curEndOfScan,1,-1
IF (lineOfText(iString:iString) .EQ. ' ') THEN
isSpace = .TRUE.
ELSE
isSpace = .FALSE.
END IF
! all logical conditions of isSpace and isInWord
IF (isSpace) THEN
IF (isInWord) THEN
!found the space in front of the word
EXIT
ELSE
!still have not found the back of the word
! do nothing
END IF
ELSE
IF (isInWord) THEN
!still have not found the space in front of the word
beginOfWord = iString
ELSE
!found the last character of the word
endOfWord = iString
beginOfWord = iString
isInWord = .TRUE.
END IF
END IF
END DO
aWord = lineOfText(beginOfWord:endOfWord)
endOfScan = beginOfWord - 1
IF (endOfScan .LT. 0) THEN
endOfScan = 0
END IF
ELSE
endOfScan = 0
aWord = ''
END IF
END SUBROUTINE GetLastWord