Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 2 additions & 0 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -192,6 +192,8 @@ list( APPEND crtm_src_files
Test_Utility/UnitTest/UnitTest_Define.f90
Utility/Binary_File_Utility.f90
Utility/Compare_Float_Numbers.f90
Utility/CSV_Utility/csv_data_define.f90
Utility/CSV_Utility/csv_data_io.f90
Utility/DateTime_Utility/DateTime_Utility.f90
Utility/DateTime_Utility/Date_Utility.f90
Utility/Endian_Utility/Endian_Utility.f90
Expand Down
48 changes: 48 additions & 0 deletions src/Utility/CSV_Utility/csv_data_define.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
module csv_data_define

implicit none

private

type, public :: csv_data
integer :: columns
integer :: rows
logical :: is_allocated = .false.
character(12) :: description
real, allocatable :: data(:,:)
contains
procedure, public, pass :: csv_data_create
final :: csv_data_destroy
end type csv_data

contains

!**************************************
!
! CONSTRUCTOR
!
!**************************************
subroutine csv_data_create(this,c,r)
integer, intent(in) :: c
integer, intent(in) :: r
class(csv_data), intent(inout) :: this
if(.not. this%is_allocated) then
allocate(this%data(r,c))
this%is_allocated = .true.
end if
end subroutine csv_data_create

!*********************************
!
! FINALIZER
!
!*********************************
subroutine csv_data_destroy(this)
type(csv_data), intent(inout) :: this
if(this%is_allocated) then
deallocate(this%data)
end if
this%is_allocated = .false.
end subroutine csv_data_destroy

end module csv_data_define
175 changes: 175 additions & 0 deletions src/Utility/CSV_Utility/csv_data_io.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,175 @@
module csv_data_io
use csv_data_define, only: csv_data
implicit none

private
public :: count_csv_columns
public :: count_csv_rows
public :: read_csv

contains

function count_csv_columns(filename) result(ncols)
implicit none
character(len=*), intent(in) :: filename
integer :: ncols
integer :: unit, ios, i, lenline
character(len=4096) :: line
CHARACTER(len=255) :: cwd

ncols = -1 ! default: error indicator

! Open the file
!inquire(file=filename, number=unit)
!if (unit == 0) unit = 21

open(newunit=unit, file=filename, status='old', action='read', iostat=ios)
if (ios /= 0) then
write(*,*) "CSV file not found!"
CALL getcwd(cwd)
WRITE(*,*) TRIM(cwd), unit
return
end if

! Read until we find a non-empty line
do
read(unit, '(A)', iostat=ios) line
if (ios /= 0) then
close(unit)
write(*,*) "Error reading CSV file lines!"
return
end if
lenline = len_trim(line)
if (lenline > 0) exit
end do

! Count commas in the line
ncols = 1
do i = 1, len_trim(line)
if (line(i:i) == ',') ncols = ncols + 1
end do

close(unit)
end function count_csv_columns

function count_csv_rows(filename) result(nrows)
implicit none
character(len=*), intent(in) :: filename
integer :: nrows
integer :: unit, ios
character(len=4096) :: line

nrows = -1 ! default (error)

! Get or assign a unit number
!inquire(file=filename, number=unit)
!if (unit == 0) unit = 21

! Open the file
open(newunit=unit, file=filename, status='old', action='read', iostat=ios)
if (ios /= 0) return

nrows = 0

! Read line-by-line
do
read(unit, '(A)', iostat=ios) line
if (ios /= 0) exit

if (len_trim(line) > 0) then
nrows = nrows + 1
end if
end do

close(unit)
end function count_csv_rows

function read_csv(filename, csv) result(status)
!! Reads numeric CSV file into csv%data (already allocated)
!!
!! Returns 0 on success, nonzero on error.
implicit none

character(len=*), intent(in) :: filename
type(csv_data), intent(inout) :: csv
integer :: status
integer :: i, j, ios
character(len=4096) :: line
character(len=64) :: token
integer :: pos, start, col

status = 0

open(unit=444, file=filename, status='old', action='read', &
iostat=ios)
if (ios /= 0) then
status = 1
return
end if

do i = 1, csv%rows
read(444, '(A)', iostat=ios) line
if (ios /= 0) then
status = 2
close(444)
return
end if

! Parse the line manually
pos = 1
col = 1

do while (col <= csv%columns)
call parse_next_token(line, pos, token)
read(token, *, iostat=ios) csv%data(i, col)
if (ios /= 0) then
status = 3
close(444)
return
end if
col = col + 1
end do
end do

close(444)
end function read_csv

subroutine parse_next_token(line, pos, token)
!! Extracts the next comma-separated token from `line`
!! starting at character index `pos`.
implicit none
character(len=*), intent(in) :: line
integer, intent(inout) :: pos
character(len=*), intent(out) :: token

integer :: lenline, start, endpos

lenline = len_trim(line)
token = ""

! Skip leading spaces
do while (pos <= lenline .and. line(pos:pos) == ' ')
pos = pos + 1
end do

start = pos

! Find next comma or end of line
do while (pos <= lenline .and. line(pos:pos) /= ',')
pos = pos + 1
end do

endpos = pos - 1

! Copy token
if (start <= endpos) then
token = adjustl(line(start:endpos))
else
token = ""
end if

! Skip comma
if (pos <= lenline .and. line(pos:pos) == ',') pos = pos + 1
end subroutine parse_next_token

end module csv_data_io