private subroutine TableGetFromFile(file, tab, id)
read a table from specified file. File is not yet open.
If id is not specified, in a file containing multiple tables,
the first table is read
Arguments:
file
file in which table is contained
tab
returned table
id
optional, id of table to read
Arguments
Type |
Intent | Optional | Attributes |
|
Name |
|
character(len=*),
|
intent(in) |
|
|
:: |
file |
|
type(Table),
|
intent(out) |
|
|
:: |
tab |
|
character(len=*),
|
intent(in), |
optional |
|
:: |
id |
|
Variables
Type |
Visibility | Attributes |
|
Name |
| Initial | |
integer(kind=long),
|
public |
|
:: |
count |
|
|
|
integer(kind=short),
|
public |
|
:: |
ios |
|
|
|
integer(kind=short),
|
public |
|
:: |
iunit |
|
|
|
integer(kind=long),
|
public |
|
:: |
j |
|
|
|
character(len=LINELENGTH),
|
public, |
POINTER
|
:: |
lines(:) |
|
|
|
character(len=300),
|
public |
|
:: |
string |
|
|
|
Source Code
SUBROUTINE TableGetFromFile &
( file, tab, id )
USE Utilities, ONLY: &
!Imported routines:
GetUnit
! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringCompact, StringToUpper
IMPLICIT NONE
! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = *), INTENT (IN) :: file
CHARACTER (LEN = *), OPTIONAL, INTENT (IN) :: id
! Array arguments with intent (out):
TYPE (Table), INTENT (OUT) :: tab
! Local scalars:
INTEGER (KIND = short) :: iunit
INTEGER (KIND = short) :: ios
INTEGER (KIND = long) :: count
INTEGER (KIND = long) :: j
CHARACTER (LEN = 300) :: string
! Local Arrays:
CHARACTER (LEN = LINELENGTH), POINTER :: lines (:)
!------------end of declaration------------------------------------------------
!get a free fortran unit
iunit = GetUnit ()
OPEN (UNIT = iunit, FILE = file, STATUS = "old")
!search beginning of table
IF (PRESENT(id)) THEN
ios = TableFileSync (iunit, id = id)
ELSE
ios = TableFileSync (iunit)
END IF
!check if table was found
IF (ios == -1) THEN
CALL Catch ('error', 'TableLib', 'Table not found in file: ', &
argument = file)
RETURN
CLOSE (iunit)
END IF
!Store significant lines in memory
CALL TableStoreLines ( iunit, lines )
!Get title
tab % title = TableReadTitle (lines)
!get Id
tab % id = TableReadId (lines)
!count number of columns
tab % noCols = TableCountCols (lines)
IF ( tab % noCols == 0) THEN
CALL Catch ('error', 'TableLib', 'no columns found in table: ', &
argument = tab % id)
END IF
!allocate columns
ALLOCATE ( tab % col ( tab % noCols ) )
!count number of rows
tab % noRows = TableCountRows (lines)
!allocate rows
DO j = 1, tab % noCols
ALLOCATE ( tab % col (j) % row ( tab % noRows ) )
END DO
!read header unit and content of the tables.
CALL TableReadHeader ( lines, tab )
CALL TableReadUnit ( lines, tab )
CALL TableReadContent ( lines, tab )
!table is initialized: close file and deallocate lines
CLOSE (iunit)
DEALLOCATE (lines)
END SUBROUTINE TableGetFromFile