Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit 60d0a76

Browse files
authored
Merge pull request #958 from zoziha/delim-1
Support csv file reading and writing in loadtxt and savetxt.
2 parents 2bdc50e + eb81933 commit 60d0a76

File tree

8 files changed

+137
-39
lines changed

8 files changed

+137
-39
lines changed

‎doc/specs/stdlib_io.md‎

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ Loads a rank-2 `array` from a text file.
1717

1818
### Syntax
1919

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

2222
### Arguments
2323

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

3232
`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.
3333

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

3636
### Return value
3737

@@ -52,7 +52,8 @@ Experimental
5252

5353
### Description
5454

55-
Returns the unit number of a file opened to read, to write, or to read and write. The file might be a text file or a binary file. All files are opened using a streamed access.
55+
Returns the unit number of a file opened to read, to write, or to read and write. The file might be a text file or a binary file.
56+
Text files are opened using a sequential access, while binary files are opened using a streamed access.
5657

5758
### Syntax
5859

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

106107
### Syntax
107108

108-
`call ` [[stdlib_io(module):savetxt(interface)]] `(filename, array)`
109+
`call ` [[stdlib_io(module):savetxt(interface)]] `(filename, array [, delimiter])`
109110

110111
### Arguments
111112

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

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

117+
`delimiter` (optional): Shall be a character expression of length 1 that contains the delimiter used to separate the columns. The default is `' '`.
118+
116119
### Output
117120

118121
Provides a text file called `filename` that contains the rank-2 `array`.

‎doc/specs/stdlib_math.md‎

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -427,7 +427,7 @@ Experimental
427427

428428
Elemenal function.
429429

430-
### Description
430+
#### Description
431431

432432
`deg2rad` converts phase angles from degrees to radians.
433433

‎doc/specs/stdlib_sparse.md‎

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -178,7 +178,7 @@ Type-bound procedures to enable requesting data from a sparse matrix.
178178

179179
`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`.
180180

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

258258
`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.
259259

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

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

361-
## Example
361+
### Example
362362
```fortran
363363
{!example/linalg/example_sparse_spmv.f90!}
364364
```

‎example/io/example.csv‎

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
1.00000000E+00, 1.00000000E+00
2+
1.00000000E+00, 1.00000000E+00
3+
1.00000000E+00, 1.00000000E+00

‎example/io/example_loadtxt.f90‎

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,4 +6,7 @@ program example_loadtxt
66

77
! Can also use list directed format if the default read fails.
88
call loadtxt('example.dat', x, fmt='*')
9+
10+
call loadtxt('example.csv', x, delimiter=',')
11+
912
end program example_loadtxt

‎example/io/example_savetxt.f90‎

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,4 +3,5 @@ program example_savetxt
33
implicit none
44
real :: x(3, 2) = 1
55
call savetxt('example.dat', x)
6+
call savetxt('example.csv', x, delimiter=',')
67
end program example_savetxt

‎src/stdlib_io.fypp‎

Lines changed: 91 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -59,13 +59,15 @@ module stdlib_io
5959
!> Format string for quadruple precision real numbers
6060
FMT_REAL_QP = '(es44.35e4)', &
6161
!> Format string for single precision complex numbers
62-
FMT_COMPLEX_SP = '(es15.8e2,1x,es15.8e2)', &
62+
FMT_COMPLEX_SP = '(es15.08e2,1x,es15.08e2)', &
6363
!> Format string for double precision complex numbers
6464
FMT_COMPLEX_DP = '(es24.16e3,1x,es24.16e3)', &
6565
!> Format string for extended double precision complex numbers
6666
FMT_COMPLEX_XDP = '(es26.18e3,1x,es26.18e3)', &
6767
!> Format string for quadruple precision complex numbers
6868
FMT_COMPLEX_QP = '(es44.35e4,1x,es44.35e4)'
69+
!> Default delimiter for loadtxt, savetxt and number_of_columns
70+
character(len=1), parameter :: delimiter_default = " "
6971

7072
public :: FMT_INT, FMT_REAL_SP, FMT_REAL_DP, FMT_REAL_XDP, FMT_REAL_QP
7173
public :: FMT_COMPLEX_SP, FMT_COMPLEX_DP, FMT_COMPLEX_XDP, FMT_COMPLEX_QP
@@ -103,7 +105,7 @@ module stdlib_io
103105
contains
104106

105107
#:for k1, t1 in KINDS_TYPES
106-
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows, fmt)
108+
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows, fmt, delimiter)
107109
!! version: experimental
108110
!!
109111
!! Loads a 2D array from a text file.
@@ -123,7 +125,9 @@ contains
123125
!! The default value is -1.
124126
integer, intent(in), optional :: max_rows
125127
character(len=*), intent(in), optional :: fmt
128+
character(len=1), intent(in), optional :: delimiter
126129
character(len=:), allocatable :: fmt_
130+
character(len=1) :: delimiter_
127131
!!
128132
!! Example
129133
!! -------
@@ -142,11 +146,13 @@ contains
142146
!! ...
143147
!!
144148
integer :: s
145-
integer :: nrow, ncol, i, ios, skiprows_, max_rows_
149+
integer :: nrow, ncol, i, j, ios, skiprows_, max_rows_, istart, iend
150+
character(len=:), allocatable :: line, iomsg_
146151
character(len=1024) :: iomsg, msgout
147152

148153
skiprows_ = max(optval(skiprows, 0), 0)
149154
max_rows_ = optval(max_rows, -1)
155+
delimiter_ = optval(delimiter, delimiter_default)
150156

151157
s = open(filename)
152158

@@ -157,12 +163,13 @@ contains
157163

158164
! determine number of columns
159165
ncol = 0
160-
if ( skiprows_ < nrow ) ncol = number_of_columns(s, skiprows=skiprows_)
166+
if ( skiprows_ < nrow ) ncol = number_of_columns(s, skiprows=skiprows_, delimiter=delimiter_)
161167
#:if 'complex' in t1
162168
ncol = ncol / 2
163169
#:endif
164170

165171
allocate(d(max_rows_, ncol))
172+
if (max_rows_ == 0 .or. ncol == 0) return
166173

167174
do i = 1, skiprows_
168175
read(s, *, iostat=ios, iomsg=iomsg)
@@ -186,15 +193,44 @@ contains
186193

187194
if ( fmt_ == '*' ) then
188195
! Use list directed read if user has specified fmt='*'
189-
do i = 1, max_rows_
190-
read (s,*,iostat=ios,iomsg=iomsg) d(i, :)
191-
192-
if (ios/=0) then
193-
write(msgout,2) trim(iomsg),size(d,2),i,trim(filename)
194-
call error_stop(msg=trim(msgout))
195-
end if
196-
197-
enddo
196+
if (is_blank(delimiter_) .or. delimiter_ == ",") then
197+
do i = 1, max_rows_
198+
read (s,*,iostat=ios,iomsg=iomsg) d(i, :)
199+
200+
if (ios/=0) then
201+
write(msgout,2) trim(iomsg),size(d,2),i,trim(filename)
202+
call error_stop(msg=trim(msgout))
203+
end if
204+
205+
enddo
206+
! Otherwise read each value separately
207+
else
208+
do i = 1, max_rows_
209+
call get_line(s, line, ios, iomsg_)
210+
if (ios/=0) then
211+
write(msgout,2) trim(iomsg_),size(d,2),i,trim(filename)
212+
call error_stop(msg=trim(msgout))
213+
end if
214+
215+
istart = 0
216+
do j = 1, ncol - 1
217+
iend = index(line(istart+1:), delimiter_)
218+
read (line(istart+1:istart+iend-1),*,iostat=ios,iomsg=iomsg) d(i, j)
219+
if (ios/=0) then
220+
write(msgout,2) trim(iomsg),size(d,2),i,trim(filename)
221+
call error_stop(msg=trim(msgout))
222+
end if
223+
istart = istart + iend
224+
end do
225+
226+
read (line(istart+1:),*,iostat=ios,iomsg=iomsg) d(i, ncol)
227+
if (ios/=0) then
228+
write(msgout,2) trim(iomsg),size(d,2),i,trim(filename)
229+
call error_stop(msg=trim(msgout))
230+
end if
231+
232+
enddo
233+
end if
198234
else
199235
! Otherwise pass default or user specified fmt string.
200236
do i = 1, max_rows_
@@ -217,7 +253,7 @@ contains
217253

218254

219255
#:for k1, t1 in KINDS_TYPES
220-
subroutine savetxt_${t1[0]}$${k1}$(filename, d)
256+
subroutine savetxt_${t1[0]}$${k1}$(filename, d, delimiter)
221257
!! version: experimental
222258
!!
223259
!! Saves a 2D array into a text file.
@@ -227,6 +263,7 @@ contains
227263
!!
228264
character(len=*), intent(in) :: filename ! File to save the array to
229265
${t1},ドル intent(in) :: d(:,:) ! The 2D array to save
266+
character(len=1), intent(in), optional :: delimiter ! Column delimiter. Default is a space.
230267
!!
231268
!! Example
232269
!! -------
@@ -236,17 +273,26 @@ contains
236273
!! call savetxt("log.txt", data)
237274
!!```
238275
!!
239-
240276
integer :: s, i, ios
277+
character(len=1) :: delimiter_
278+
character(len=3) :: delim_str
279+
character(len=:), allocatable :: fmt_
241280
character(len=1024) :: iomsg, msgout
281+
282+
delimiter_ = optval(delimiter, delimiter_default)
283+
delim_str = "'"//delimiter_//"'"
284+
#:if 'real' in t1
285+
fmt_ = "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",:,"//delim_str//"))"
286+
#:elif 'complex' in t1
287+
fmt_ = "(*"//FMT_COMPLEX_${k1}$(1:11)//delim_str//FMT_COMPLEX_${k1}$(14:23)//",:,"//delim_str//"))"
288+
#:elif 'integer' in t1
289+
fmt_ = "(*"//FMT_INT(1:len(FMT_INT)-1)//",:,"//delim_str//"))"
290+
#:endif
291+
242292
s = open(filename, "w")
243293
do i = 1, size(d, 1)
244-
#:if 'real' in t1
245-
write(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",:,1x))", &
246-
#:elif 'complex' in t1
247-
write(s, "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",:,1x))", &
248-
#:elif 'integer' in t1
249-
write(s, "(*"//FMT_INT(1:len(FMT_INT)-1)//",:,1x))", &
294+
#:if 'real' in t1 or 'complex' in t1 or 'integer' in t1
295+
write(s, fmt_, &
250296
#:else
251297
write(s, *, &
252298
#:endif
@@ -266,19 +312,22 @@ contains
266312
#:endfor
267313

268314

269-
integer function number_of_columns(s, skiprows)
315+
integer function number_of_columns(s, skiprows, delimiter)
270316
!! version: experimental
271317
!!
272318
!! determine number of columns
273319
integer,intent(in) :: s
274320
integer, intent(in), optional :: skiprows
321+
character(len=1), intent(in), optional :: delimiter
275322

276323
integer :: ios, skiprows_, i
277324
character :: c
278325
character(len=:), allocatable :: line
279-
logical :: lastblank
326+
character(len=1) :: delimiter_
327+
logical :: last_delim
280328

281329
skiprows_ = optval(skiprows, 0)
330+
delimiter_ = optval(delimiter, delimiter_default)
282331

283332
rewind(s)
284333

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

294-
lastblank = .true.
295-
do i = 1,len(line)
296-
c = line(i:i)
297-
if (lastblank .and. .not. is_blank(c)) number_of_columns = number_of_columns + 1
298-
lastblank = is_blank(c)
299-
end do
343+
last_delim = .true.
344+
if (delimiter_ == delimiter_default) then
345+
do i = 1,len(line)
346+
c = line(i:i)
347+
if (last_delim .and. .not. is_blank(c)) number_of_columns = number_of_columns + 1
348+
last_delim = is_blank(c)
349+
end do
350+
else
351+
do i = 1,len(line)
352+
if (line(i:i) == delimiter_) number_of_columns = number_of_columns + 1
353+
end do
354+
if (number_of_columns == 0) then
355+
if (len_trim(line) /= 0) number_of_columns = 1
356+
else
357+
number_of_columns = number_of_columns + 1
358+
end if
359+
end if
300360
rewind(s)
301361

302362
end function number_of_columns
@@ -400,14 +460,14 @@ contains
400460
select case (mode_(3:3))
401461
case('t')
402462
form_='formatted'
463+
access_='sequential'
403464
case('b')
404465
form_='unformatted'
466+
access_ = 'stream'
405467
case default
406468
call error_stop("Unsupported mode: "//mode_(3:3))
407469
end select
408470

409-
access_ = 'stream'
410-
411471
if (present(iostat)) then
412472
open(newunit=u, file=filename, &
413473
action = action_, position = position_, status = status_, &

‎test/io/test_loadtxt.f90‎

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,14 @@ subroutine test_loadtxt_int32(error)
4747
call loadtxt('test_int32.txt', expected, fmt='*')
4848
call check(error, all(input == expected),'User specified list directed read faile')
4949
if (allocated(error)) return
50+
call savetxt('test_int32.txt', input, delimiter=',')
51+
call loadtxt('test_int32.txt', expected, delimiter=',')
52+
call check(error, all(input == expected),'User specified delimiter `,` read failed')
53+
if (allocated(error)) return
54+
call savetxt('test_int32.txt', input, delimiter='-')
55+
call loadtxt('test_int32.txt', expected, delimiter='-')
56+
call check(error, all(input == expected),'User specified delimiter `-` read failed')
57+
if (allocated(error)) return
5058
end do
5159

5260
end subroutine test_loadtxt_int32
@@ -74,6 +82,14 @@ subroutine test_loadtxt_sp(error)
7482
call loadtxt('test_sp.txt', expected, fmt="(*"//FMT_REAL_sp(1:len(FMT_REAL_sp)-1)//",1x))")
7583
call check(error, all(input == expected),'User specified format failed')
7684
if (allocated(error)) return
85+
call savetxt('test_sp.txt', input, delimiter=',')
86+
call loadtxt('test_sp.txt', expected, delimiter=',')
87+
call check(error, all(input == expected),'User specified delimiter `,` read failed')
88+
if (allocated(error)) return
89+
call savetxt('test_sp.txt', input, delimiter=';')
90+
call loadtxt('test_sp.txt', expected, delimiter=';')
91+
call check(error, all(input == expected),'User specified delimiter `;` read failed')
92+
if (allocated(error)) return
7793
end do
7894

7995
end subroutine test_loadtxt_sp
@@ -158,6 +174,10 @@ subroutine test_loadtxt_dp(error)
158174
call loadtxt('test_dp.txt', expected, fmt="(*"//FMT_REAL_dp(1:len(FMT_REAL_dp)-1)//",1x))")
159175
call check(error, all(input == expected),'User specified format failed')
160176
if (allocated(error)) return
177+
call savetxt('test_dp.txt', input, delimiter=',')
178+
call loadtxt('test_dp.txt', expected, delimiter=',')
179+
call check(error, all(input == expected),'User specified delimiter read failed')
180+
if (allocated(error)) return
161181
end do
162182

163183
end subroutine test_loadtxt_dp
@@ -272,6 +292,14 @@ subroutine test_loadtxt_complex(error)
272292
call loadtxt('test_complex.txt', expected, fmt="(*"//FMT_COMPLEX_dp(1:len(FMT_COMPLEX_dp)-1)//",1x))")
273293
call check(error, all(input == expected))
274294
if (allocated(error)) return
295+
call savetxt('test_complex.txt', input, delimiter=',')
296+
call loadtxt('test_complex.txt', expected, delimiter=',')
297+
call check(error, all(input == expected))
298+
if (allocated(error)) return
299+
call savetxt('test_complex.txt', input, delimiter=';')
300+
call loadtxt('test_complex.txt', expected, delimiter=';')
301+
call check(error, all(input == expected))
302+
if (allocated(error)) return
275303
end do
276304

277305
end subroutine test_loadtxt_complex

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /