StringSplit Subroutine

public subroutine StringSplit(delims, string, before, sep)

Finds the first instance of a character from 'delims' in the the string 'string'. The characters before the found delimiter are output in 'before'. The characters after the found delimiter are output in 'string'. The optional output character 'sep' contains the found delimiter. Arguments: string String to be treated Result: The characters before the found delimiter, the remainder is output in string

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: delims
character(len=*), intent(inout) :: string
character(len=*), intent(out) :: before
character(len=*), intent(out), optional :: sep

Variables

Type Visibility Attributes Name Initial
character(len=1), public :: ch
character(len=1), public :: cha
integer(kind=short), public :: i
integer(kind=short), public :: ipos
integer(kind=short), public :: iposa
integer(kind=short), public :: k
integer(kind=short), public :: length
logical, public :: pres

Source Code

SUBROUTINE StringSplit &
!
  ( delims, string, before, sep )

IMPLICIT NONE

! Subroutine arguments
! Scalar arguments with intent(in):
CHARACTER(LEN=*), INTENT (IN) :: delims

! Scalar arguments with intent(inout):
CHARACTER(LEN=*), INTENT (INOUT) :: string

! Scalar arguments with intent(out):
CHARACTER(LEN=*), INTENT (OUT) :: before
CHARACTER(LEN=*), OPTIONAL, INTENT (OUT) :: sep

! Local scalars:
CHARACTER (LEN = 1)         :: ch
CHARACTER (LEN = 1)         :: cha
LOGICAL                     :: pres
INTEGER (KIND = short)      :: iposa
INTEGER (KIND = short)      :: ipos
INTEGER (KIND = short)      :: i,k 
INTEGER (KIND = short)      :: length
!------------end of declaration------------------------------------------------

pres = PRESENT(sep)
string = ADJUSTL (string)
string = StringCompact (string)
length = LEN_TRIM (string)
IF (length == 0) RETURN        ! string is empty
k = 0
before = ' '
DO i = 1,length
   ch = string(i:i)
   ipos = INDEX (delims,ch)         
   IF (ipos == 0) THEN         ! character is not a delimiter
      k = k + 1
      before(k:k) = ch
      CYCLE
   END IF
   IF (ch /= ' ') THEN         ! character is a delimiter that is not a space
      string = string (i+1:)
      IF (pres) sep = ch
      EXIT
   END IF
   cha = string (i+1 : i+1)    ! character is a space delimiter
   iposa = INDEX (delims,cha)
   IF (iposa > 0) THEN         ! next character is a delimiter
      string = string (i+2:)
      IF (pres) sep = cha
      EXIT
   ELSE
      string = string (i+1:)
      IF (pres) sep = ch
      EXIT
   END IF
END DO
IF (i >= length) string = ''
string = ADJUSTL (string)      ! remove initial spaces
RETURN

END SUBROUTINE StringSplit