@@ -103,7 +103,7 @@ module stdlib_io
103
103
contains
104
104
105
105
#: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 )
107
107
!! version: experimental
108
108
!!
109
109
!! Loads a 2D array from a text file.
@@ -123,6 +123,7 @@ contains
123
123
!! The default value is -1.
124
124
integer, intent(in), optional :: max_rows
125
125
character(len=*), intent(in), optional :: fmt
126
+ character(len=1), intent(in), optional :: delimiter
126
127
character(len=:), allocatable :: fmt_
127
128
!!
128
129
!! Example
@@ -157,9 +158,11 @@ contains
157
158
158
159
! determine number of columns
159
160
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 )
161
162
#:if 'complex' in t1
162
- ncol = ncol / 2
163
+ if (present(delimiter)) then
164
+ if (is_blank(delimiter)) ncol = ncol / 2
165
+ end if
163
166
#:endif
164
167
165
168
allocate(d(max_rows_, ncol))
@@ -217,7 +220,7 @@ contains
217
220
218
221
219
222
#:for k1, t1 in KINDS_TYPES
220
- subroutine savetxt_${t1[0]}$${k1}$(filename, d)
223
+ subroutine savetxt_${t1[0]}$${k1}$(filename, d, delimiter )
221
224
!! version: experimental
222
225
!!
223
226
!! Saves a 2D array into a text file.
@@ -227,6 +230,7 @@ contains
227
230
!!
228
231
character(len=*), intent(in) :: filename ! File to save the array to
229
232
${t1}$, intent(in) :: d(:,:) ! The 2D array to save
233
+ character(len=1), intent(in), optional :: delimiter ! Column delimiter. Default is a space.
230
234
!!
231
235
!! Example
232
236
!! -------
@@ -236,17 +240,27 @@ contains
236
240
!! call savetxt("log.txt", data)
237
241
!!```
238
242
!!
239
-
243
+
240
244
integer :: s, i, ios
245
+ character(len=1) :: delimiter_
246
+ character(len=3) :: delim_str
247
+ character(len=:), allocatable :: fmt_
241
248
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
+
242
260
s = open(filename, "w")
243
261
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_, &
250
264
#:else
251
265
write(s, *, &
252
266
#:endif
@@ -266,19 +280,22 @@ contains
266
280
#:endfor
267
281
268
282
269
- integer function number_of_columns(s, skiprows)
283
+ integer function number_of_columns(s, skiprows, delimiter )
270
284
!! version: experimental
271
285
!!
272
286
!! determine number of columns
273
287
integer,intent(in) :: s
274
288
integer, intent(in), optional :: skiprows
289
+ character(len=1), intent(in), optional :: delimiter
275
290
276
291
integer :: ios, skiprows_, i
277
292
character :: c
278
293
character(len=:), allocatable :: line
279
- logical :: lastblank
294
+ character(len=1) :: delimiter_
295
+ logical :: last_delim
280
296
281
297
skiprows_ = optval(skiprows, 0)
298
+ delimiter_ = optval(delimiter, " ")
282
299
283
300
rewind(s)
284
301
@@ -291,12 +308,23 @@ contains
291
308
call get_line(s, line, ios)
292
309
if (ios/=0 .or. .not.allocated(line)) return
293
310
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
300
328
rewind(s)
301
329
302
330
end function number_of_columns
0 commit comments