read_csv_file Subroutine

private subroutine read_csv_file(me, filename, header_row, skip_rows, status_ok, delimiter)

Read a CSV file.

rows in the file

row counter in data array

Type Bound

csv_file

Arguments

Type IntentOptional Attributes Name
class(csv_file), intent(inout) :: me
character(len=*), intent(in) :: filename

the CSV file to open

integer, intent(in), optional :: header_row

the header row

integer, intent(in), optional, dimension(:) :: skip_rows

rows to skip

logical, intent(out) :: status_ok

status flag

character(len=1), intent(in), optional :: delimiter

(Default is ,)


Calls

proc~~read_csv_file~~CallsGraph proc~read_csv_file csv_file%read_csv_file proc~number_of_lines_in_file number_of_lines_in_file proc~read_csv_file->proc~number_of_lines_in_file proc~read_line_from_file csv_file%read_line_from_file proc~read_csv_file->proc~read_line_from_file proc~tokenize_csv_line csv_file%tokenize_csv_line proc~read_csv_file->proc~tokenize_csv_line proc~unique unique proc~read_csv_file->proc~unique proc~split split proc~tokenize_csv_line->proc~split proc~expand_vector expand_vector proc~unique->proc~expand_vector proc~sort_ascending sort_ascending proc~unique->proc~sort_ascending proc~swap swap proc~sort_ascending->proc~swap proc~split->proc~expand_vector

Source Code

    subroutine read_csv_file(me,filename,header_row,skip_rows,status_ok,delimiter)

    implicit none

    class(csv_file),intent(inout) :: me
    character(len=*),intent(in) :: filename  !! the CSV file to open
    logical,intent(out) :: status_ok  !! status flag
    integer,intent(in),optional :: header_row  !! the header row
    integer,dimension(:),intent(in),optional :: skip_rows  !! rows to skip
    character(len=1),intent(in),optional :: delimiter         !! note: can only be one character
                                                              !! (Default is `,`)

    type(csv_string),dimension(:),allocatable :: row_data  !! a tokenized row
    integer,dimension(:),allocatable :: rows_to_skip  !! the actual rows to skip
    character(len=:),allocatable :: line  !! a line from the file
    integer :: i                !! counter
    integer :: j                !! counter
    integer :: irow             !! row counter
    integer :: n_rows_in_file   !! number of lines in the file
    integer :: n_rows           !! number of rows in the output data matrix
    integer :: n_cols           !! number of columns in the file (and output data matrix)
    integer :: istat            !! open status flag
    integer :: iunit            !! open file unit
    logical :: arrays_allocated !! if the arrays in the
                                !! class have been allocated
    integer :: iheader          !! row number of header row
                                !! (0 if no header specified)
    character(len=1) :: tmp     !! for skipping a row

    ! clear existing data:
    arrays_allocated = .false.
    if (allocated(me%csv_data)) deallocate(me%csv_data)
    if (allocated(me%header))   deallocate(me%header)
    if (present(delimiter)) me%delimiter = delimiter

    open(newunit=iunit, file=filename, status='OLD', iostat=istat)

    if (istat==0) then

        !get number of lines in the file
        n_rows_in_file = number_of_lines_in_file(iunit)

        !get number of lines in the data array
        if (present(skip_rows)) then
            !get size of unique elements in skip_rows,
            !and subtract from n_rows_in_file
            rows_to_skip = unique(skip_rows,chunk_size=me%chunk_size)
            n_rows = n_rows_in_file - size(rows_to_skip)
        else
            n_rows = n_rows_in_file
        end if
        if (present(header_row)) then
            iheader = max(0,header_row)
            n_rows = n_rows - merge(0,1,iheader==0)
        else
            iheader = 0
        end if

        me%n_rows = n_rows

        ! we don't know the number of columns
        ! until we parse the first row (or the header)

        !read each line in the file, parse it, and populate data
        irow = 0
        do i=1,n_rows_in_file  !! rows in the file

            ! skip row if necessary
            if (allocated(rows_to_skip)) then
                if (any(i==rows_to_skip)) then
                    read(iunit,fmt='(A1)',iostat=istat) tmp
                    if (istat/=0) then
                        if (me%verbose) write(error_unit,'(A)') &
                                'Error skipping row in file: '//trim(filename)
                        close(unit=iunit,iostat=istat)
                        status_ok = .false.
                        return
                    end if
                    cycle
                end if
            end if

            call me%read_line_from_file(iunit,line,status_ok)
            if (.not. status_ok) return ! file read error
            call me%tokenize(line,row_data)

            if (.not. arrays_allocated) then
                ! note: the number of columns is obtained
                ! from the first one read. It is assumed
                ! that each row has the same number of
                ! columns.
                n_cols = size(row_data)
                me%n_cols = n_cols
                allocate(me%csv_data(n_rows,n_cols))
                if (iheader/=0) allocate(me%header(n_cols))
                arrays_allocated = .true.
            end if

            if (i==iheader) then
                do j=1,me%n_cols
                    me%header(j)%str = row_data(j)%str
                end do
            else
                irow = irow + 1  !! row counter in data array
                do j=1,n_cols
                    me%csv_data(irow,j) = row_data(j) !%str
                end do
            end if

        end do

        ! close the file
        close(unit=iunit,iostat=istat)

        status_ok = .true.

    else
        if (me%verbose) write(error_unit,'(A)') &
                'Error opening file: '//trim(filename)
        status_ok = .false.
    end if

    end subroutine read_csv_file