Skip to content
New issue

Have a question about this project? # for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “#”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? # to your account

Support csv file reading and writing in loadtxt and savetxt. #958

Merged
merged 6 commits into from
Mar 28, 2025
Merged
Changes from 3 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
8 changes: 5 additions & 3 deletions doc/specs/stdlib_io.md
Original file line number Diff line number Diff line change
@@ -17,7 +17,7 @@ Loads a rank-2 `array` from a text file.

### Syntax

`call ` [[stdlib_io(module):loadtxt(interface)]] `(filename, array [, skiprows] [, max_rows] [, fmt])`
`call ` [[stdlib_io(module):loadtxt(interface)]] `(filename, array [, skiprows] [, max_rows] [, fmt] [, delimiter])`

### Arguments

@@ -31,7 +31,7 @@ Loads a rank-2 `array` from a text file.

`fmt` (optional): Fortran format specifier for the text read. Defaults to the write format for the data type. Setting fmt='*' will specify list directed read.


`delimiter` (optional): Shall be a character expression of length 1 that contains the delimiter used to separate the columns. The default is `' '`.

### Return value

@@ -105,14 +105,16 @@ Saves a rank-2 `array` into a text file.

### Syntax

`call ` [[stdlib_io(module):savetxt(interface)]] `(filename, array)`
`call ` [[stdlib_io(module):savetxt(interface)]] `(filename, array [, delimiter])`

### Arguments

`filename`: Shall be a character expression containing the name of the file that will contain the 2D `array`.

`array`: Shall be a rank-2 array of type `real`, `complex` or `integer`.

`delimiter` (optional): Shall be a character expression of length 1 that contains the delimiter used to separate the columns. The default is `' '`.

### Output

Provides a text file called `filename` that contains the rank-2 `array`.
2 changes: 1 addition & 1 deletion doc/specs/stdlib_math.md
Original file line number Diff line number Diff line change
@@ -427,7 +427,7 @@ Experimental

Elemenal function.

### Description
#### Description

`deg2rad` converts phase angles from degrees to radians.

6 changes: 3 additions & 3 deletions doc/specs/stdlib_sparse.md
Original file line number Diff line number Diff line change
@@ -178,7 +178,7 @@ Type-bound procedures to enable requesting data from a sparse matrix.

`v` : Shall be a `real` or `complex` value in accordance to the declared sparse matrix object. If the `ij` tuple is within the sparse pattern, `v` contains the value in the data buffer. If the `ij` tuple is outside the sparse pattern, `v` is equal `0`. If the `ij` tuple is outside the matrix pattern `(nrows,ncols)`, `v` is `NaN`.

## Example
### Example
```fortran
{!example/linalg/example_sparse_data_accessors.f90!}
```
@@ -257,7 +257,7 @@ This module provides facility functions for converting between storage formats.

`chunk`, `optional`: chunk size, only valid in the case of a `SELLC` matrix, by default it will be taken from the `SELLC` default attribute chunk size. It is an `intent(in)` argument.

## Example
### Example
```fortran
{!example/linalg/example_sparse_from_ijv.f90!}
```
@@ -358,7 +358,7 @@ If the `diagonal` array has not been previously allocated, the `diag` subroutine

`coo` : Shall be a `COO` type of `real` or `complex` type. It is an `intent(out)` argument.

## Example
### Example
```fortran
{!example/linalg/example_sparse_spmv.f90!}
```
3 changes: 3 additions & 0 deletions example/io/example.csv
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
1.00000000E+00, 1.00000000E+00
1.00000000E+00, 1.00000000E+00
1.00000000E+00, 1.00000000E+00
3 changes: 3 additions & 0 deletions example/io/example_loadtxt.f90
Original file line number Diff line number Diff line change
@@ -6,4 +6,7 @@ program example_loadtxt

! Can also use list directed format if the default read fails.
call loadtxt('example.dat', x, fmt='*')

call loadtxt('example.csv', x, delimiter=',')

end program example_loadtxt
1 change: 1 addition & 0 deletions example/io/example_savetxt.f90
Original file line number Diff line number Diff line change
@@ -3,4 +3,5 @@ program example_savetxt
implicit none
real :: x(3, 2) = 1
call savetxt('example.dat', x)
call savetxt('example.csv', x, delimiter=',')
end program example_savetxt
66 changes: 47 additions & 19 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
@@ -103,7 +103,7 @@ module stdlib_io
contains

#:for k1, t1 in KINDS_TYPES
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows, fmt)
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows, fmt, delimiter)
!! version: experimental
!!
!! Loads a 2D array from a text file.
@@ -123,7 +123,9 @@ contains
!! The default value is -1.
integer, intent(in), optional :: max_rows
character(len=*), intent(in), optional :: fmt
character(len=1), intent(in), optional :: delimiter
character(len=:), allocatable :: fmt_
character(len=1) :: delimiter_
!!
!! Example
!! -------
@@ -147,6 +149,7 @@ contains

skiprows_ = max(optval(skiprows, 0), 0)
max_rows_ = optval(max_rows, -1)
delimiter_ = optval(delimiter, " ")

s = open(filename)

@@ -157,9 +160,9 @@ contains

! determine number of columns
ncol = 0
if ( skiprows_ < nrow ) ncol = number_of_columns(s, skiprows=skiprows_)
if ( skiprows_ < nrow ) ncol = number_of_columns(s, skiprows=skiprows_, delimiter=delimiter_)
#:if 'complex' in t1
ncol = ncol / 2
if (is_blank(delimiter_)) ncol = ncol / 2
#:endif

allocate(d(max_rows_, ncol))
@@ -217,7 +220,7 @@ contains


#:for k1, t1 in KINDS_TYPES
subroutine savetxt_${t1[0]}$${k1}$(filename, d)
subroutine savetxt_${t1[0]}$${k1}$(filename, d, delimiter)
!! version: experimental
!!
!! Saves a 2D array into a text file.
@@ -227,6 +230,7 @@ contains
!!
character(len=*), intent(in) :: filename ! File to save the array to
${t1}$, intent(in) :: d(:,:) ! The 2D array to save
character(len=1), intent(in), optional :: delimiter ! Column delimiter. Default is a space.
!!
!! Example
!! -------
@@ -236,17 +240,27 @@ contains
!! call savetxt("log.txt", data)
!!```
!!

integer :: s, i, ios
character(len=1) :: delimiter_
character(len=3) :: delim_str
character(len=:), allocatable :: fmt_
character(len=1024) :: iomsg, msgout

delimiter_ = optval(delimiter, " ")
delim_str = "'"//delimiter_//"'"
#:if 'real' in t1
fmt_ = "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",:,"//delim_str//"))"
#:elif 'complex' in t1
fmt_ = "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",:,"//delim_str//"))"
#:elif 'integer' in t1
fmt_ = "(*"//FMT_INT(1:len(FMT_INT)-1)//",:,"//delim_str//"))"
#:endif

s = open(filename, "w")
do i = 1, size(d, 1)
#:if 'real' in t1
write(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",:,1x))", &
#:elif 'complex' in t1
write(s, "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",:,1x))", &
#:elif 'integer' in t1
write(s, "(*"//FMT_INT(1:len(FMT_INT)-1)//",:,1x))", &
#:if 'real' in t1 or 'complex' in t1 or 'integer' in t1
write(s, fmt_, &
#:else
write(s, *, &
#:endif
@@ -266,19 +280,22 @@ contains
#:endfor


integer function number_of_columns(s, skiprows)
integer function number_of_columns(s, skiprows, delimiter)
!! version: experimental
!!
!! determine number of columns
integer,intent(in) :: s
integer, intent(in), optional :: skiprows
character(len=1), intent(in), optional :: delimiter

integer :: ios, skiprows_, i
character :: c
character(len=:), allocatable :: line
logical :: lastblank
character(len=1) :: delimiter_
logical :: last_delim

skiprows_ = optval(skiprows, 0)
delimiter_ = optval(delimiter, " ")

rewind(s)

@@ -291,12 +308,23 @@ contains
call get_line(s, line, ios)
if (ios/=0 .or. .not.allocated(line)) return

lastblank = .true.
do i = 1,len(line)
c = line(i:i)
if (lastblank .and. .not. is_blank(c)) number_of_columns = number_of_columns + 1
lastblank = is_blank(c)
end do
last_delim = .true.
if (delimiter_ == " ") then
do i = 1,len(line)
c = line(i:i)
if (last_delim .and. .not. is_blank(c)) number_of_columns = number_of_columns + 1
last_delim = is_blank(c)
end do
else
do i = 1,len(line)
if (line(i:i) == delimiter_) number_of_columns = number_of_columns + 1
end do
if (number_of_columns == 0) then
if (len_trim(line) /= 0) number_of_columns = 1
else
number_of_columns = number_of_columns + 1
end if
end if
rewind(s)

end function number_of_columns
16 changes: 16 additions & 0 deletions test/io/test_loadtxt.f90
Original file line number Diff line number Diff line change
@@ -47,6 +47,10 @@ subroutine test_loadtxt_int32(error)
call loadtxt('test_int32.txt', expected, fmt='*')
call check(error, all(input == expected),'User specified list directed read faile')
if (allocated(error)) return
call savetxt('test_int32.txt', input, delimiter=',')
call loadtxt('test_int32.txt', expected, delimiter=',')
call check(error, all(input == expected),'User specified delimiter read failed')
if (allocated(error)) return
end do

end subroutine test_loadtxt_int32
@@ -74,6 +78,10 @@ subroutine test_loadtxt_sp(error)
call loadtxt('test_sp.txt', expected, fmt="(*"//FMT_REAL_sp(1:len(FMT_REAL_sp)-1)//",1x))")
call check(error, all(input == expected),'User specified format failed')
if (allocated(error)) return
call savetxt('test_sp.txt', input, delimiter=',')
call loadtxt('test_sp.txt', expected, delimiter=',')
call check(error, all(input == expected),'User specified delimiter read failed')
if (allocated(error)) return
end do

end subroutine test_loadtxt_sp
@@ -158,6 +166,10 @@ subroutine test_loadtxt_dp(error)
call loadtxt('test_dp.txt', expected, fmt="(*"//FMT_REAL_dp(1:len(FMT_REAL_dp)-1)//",1x))")
call check(error, all(input == expected),'User specified format failed')
if (allocated(error)) return
call savetxt('test_dp.txt', input, delimiter=',')
call loadtxt('test_dp.txt', expected, delimiter=',')
call check(error, all(input == expected),'User specified delimiter read failed')
if (allocated(error)) return
end do

end subroutine test_loadtxt_dp
@@ -272,6 +284,10 @@ subroutine test_loadtxt_complex(error)
call loadtxt('test_complex.txt', expected, fmt="(*"//FMT_COMPLEX_dp(1:len(FMT_COMPLEX_dp)-1)//",1x))")
call check(error, all(input == expected))
if (allocated(error)) return
call savetxt('test_complex.txt', input, delimiter=',')
call loadtxt('test_complex.txt', expected, delimiter=',')
call check(error, all(input == expected))
if (allocated(error)) return
end do

end subroutine test_loadtxt_complex
Loading