private function TableCountCols(lines) result(cols)
Count the number of columns in a table stored in a collection of lines.
Method:
count the number of tokens included in parentheses [].
Arguments:
lines
collections of lines
Result:
Return number of columns
Arguments
Type |
Intent | Optional | Attributes |
|
Name |
|
character(len=LINELENGTH),
|
intent(in), |
|
POINTER
|
:: |
lines(:) |
|
Return Value
integer(kind=short)
Variables
Type |
Visibility | Attributes |
|
Name |
| Initial | |
character(len=300),
|
public |
|
:: |
before |
|
|
|
character(len=1),
|
public |
|
:: |
ch |
|
|
|
logical,
|
public |
|
:: |
columnsFound |
|
|
|
integer(kind=short),
|
public |
|
:: |
i |
|
|
|
logical,
|
public |
|
:: |
parOpen |
|
|
|
character(len=LINELENGTH),
|
public |
|
:: |
string |
|
|
|
Source Code
FUNCTION TableCountCols &
( lines ) &
RESULT (cols)
! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringCompact, StringToUpper, StringSplit
IMPLICIT NONE
! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = LINELENGTH), INTENT (IN), POINTER :: lines (:)
! Local scalars:
INTEGER (KIND = short) :: cols
INTEGER (KIND = short) :: i
CHARACTER (LEN = LINELENGTH) :: string
CHARACTER (LEN = 300) :: before
CHARACTER (LEN = 1) :: ch
LOGICAL :: columnsFound
LOGICAL :: parOpen
!------------end of declaration------------------------------------------------
string = ''
columnsFound = .FALSE.
cols = 0
! scan table to find line denoted to columns keyword.
DO i = 1, SIZE (lines)
string = lines (i)
CALL StringSplit ( ':', string, before)
IF ( StringToUpper ( before(1:7)) == "COLUMNS" ) THEN !found columns
CALL StringSplit ( '#', string, before) !remove inline comments
string = before
columnsFound = .TRUE.
EXIT
END IF
END DO
IF ( .NOT. columnsFound ) THEN
CALL Catch ('error', 'TableLib', 'Keyword columns not found')
END IF
!count the number of couples of parentheses (), [], {} or <>
parOpen = .FALSE.
DO i = 1, LEN_TRIM (string)
ch = string (i:i)
IF ( ch == "[" ) THEN
IF (parOpen ) THEN
CALL Catch ('error', 'TableLib', 'parentheses in columns was not closed')
END IF
parOpen = .TRUE.
cols = cols + 1
ELSE IF ( ch == "]") THEN
IF (.NOT. parOpen ) THEN
CALL Catch ('error', 'TableLib', 'parentheses in columns was not opened')
END IF
parOpen = .FALSE.
END IF
END DO
!if parentheses are not closed, log an error
IF (parOpen ) THEN
CALL Catch ('error', 'TableLib', 'parentheses in columns was not closed')
END IF
END FUNCTION TableCountCols