Skip to content

Commit ffc53a7

Browse files
committed
Add the delimiter argument to the loadtxt and savetxt functions.
1 parent 5c64ee6 commit ffc53a7

File tree

6 files changed

+75
-22
lines changed

6 files changed

+75
-22
lines changed

doc/specs/stdlib_io.md

+5-3
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

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

106106
### Syntax
107107

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

110110
### Arguments
111111

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

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

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

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

example/io/example.csv

+3
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

+3
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

+1
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

+47-19
Original file line numberDiff line numberDiff line change
@@ -103,7 +103,7 @@ module stdlib_io
103103
contains
104104

105105
#:for k1, t1 in KINDS_TYPES
106-
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows, fmt)
106+
subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows, fmt, delimiter)
107107
!! version: experimental
108108
!!
109109
!! Loads a 2D array from a text file.
@@ -123,6 +123,7 @@ contains
123123
!! The default value is -1.
124124
integer, intent(in), optional :: max_rows
125125
character(len=*), intent(in), optional :: fmt
126+
character(len=1), intent(in), optional :: delimiter
126127
character(len=:), allocatable :: fmt_
127128
!!
128129
!! Example
@@ -157,9 +158,11 @@ contains
157158

158159
! determine number of columns
159160
ncol = 0
160-
if ( skiprows_ < nrow ) ncol = number_of_columns(s, skiprows=skiprows_)
161+
if ( skiprows_ < nrow ) ncol = number_of_columns(s, skiprows=skiprows_, delimiter=delimiter)
161162
#:if 'complex' in t1
162-
ncol = ncol / 2
163+
if (present(delimiter)) then
164+
if (is_blank(delimiter)) ncol = ncol / 2
165+
end if
163166
#:endif
164167

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

218221

219222
#:for k1, t1 in KINDS_TYPES
220-
subroutine savetxt_${t1[0]}$${k1}$(filename, d)
223+
subroutine savetxt_${t1[0]}$${k1}$(filename, d, delimiter)
221224
!! version: experimental
222225
!!
223226
!! Saves a 2D array into a text file.
@@ -227,6 +230,7 @@ contains
227230
!!
228231
character(len=*), intent(in) :: filename ! File to save the array to
229232
${t1}$, intent(in) :: d(:,:) ! The 2D array to save
233+
character(len=1), intent(in), optional :: delimiter ! Column delimiter. Default is a space.
230234
!!
231235
!! Example
232236
!! -------
@@ -236,17 +240,27 @@ contains
236240
!! call savetxt("log.txt", data)
237241
!!```
238242
!!
239-
243+
240244
integer :: s, i, ios
245+
character(len=1) :: delimiter_
246+
character(len=3) :: delim_str
247+
character(len=:), allocatable :: fmt_
241248
character(len=1024) :: iomsg, msgout
249+
250+
delimiter_ = optval(delimiter, " ")
251+
delim_str = "'"//delimiter_//"'"
252+
#:if 'real' in t1
253+
fmt_ = "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",:,"//delim_str//"))"
254+
#:elif 'complex' in t1
255+
fmt_ = "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",:,"//delim_str//"))"
256+
#:elif 'integer' in t1
257+
fmt_ = "(*"//FMT_INT(1:len(FMT_INT)-1)//",:,"//delim_str//"))"
258+
#:endif
259+
242260
s = open(filename, "w")
243261
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))", &
262+
#:if 'real' in t1 or 'complex' in t1 or 'integer' in t1
263+
write(s, fmt_, &
250264
#:else
251265
write(s, *, &
252266
#:endif
@@ -266,19 +280,22 @@ contains
266280
#:endfor
267281

268282

269-
integer function number_of_columns(s, skiprows)
283+
integer function number_of_columns(s, skiprows, delimiter)
270284
!! version: experimental
271285
!!
272286
!! determine number of columns
273287
integer,intent(in) :: s
274288
integer, intent(in), optional :: skiprows
289+
character(len=1), intent(in), optional :: delimiter
275290

276291
integer :: ios, skiprows_, i
277292
character :: c
278293
character(len=:), allocatable :: line
279-
logical :: lastblank
294+
character(len=1) :: delimiter_
295+
logical :: last_delim
280296

281297
skiprows_ = optval(skiprows, 0)
298+
delimiter_ = optval(delimiter, " ")
282299

283300
rewind(s)
284301

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

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
311+
last_delim = .true.
312+
if (delimiter_ == " ") then
313+
do i = 1,len(line)
314+
c = line(i:i)
315+
if (last_delim .and. .not. is_blank(c)) number_of_columns = number_of_columns + 1
316+
last_delim = is_blank(c)
317+
end do
318+
else
319+
do i = 1,len(line)
320+
if (line(i:i) == delimiter_) number_of_columns = number_of_columns + 1
321+
end do
322+
if (number_of_columns == 0) then
323+
if (len_trim(line) /= 0) number_of_columns = 1
324+
else
325+
number_of_columns = number_of_columns + 1
326+
end if
327+
end if
300328
rewind(s)
301329

302330
end function number_of_columns

test/io/test_loadtxt.f90

+16
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,10 @@ 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
5054
end do
5155

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

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

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

277293
end subroutine test_loadtxt_complex

0 commit comments

Comments
 (0)