1
1
module stdlib_experimental_io
2
- use stdlib_experimental_kinds, only: sp, dp, qp
2
+
3
+
4
+ use stdlib_experimental_kinds, only: sp, dp, qp, &
5
+ int8, int16, int32, int64
3
6
use stdlib_experimental_error, only: error_stop
4
7
use stdlib_experimental_optval, only: optval
5
8
use stdlib_experimental_ascii, only: is_blank
@@ -11,22 +14,29 @@ module stdlib_experimental_io
11
14
! Private API that is exposed so that we can test it in tests
12
15
public :: parse_mode
13
16
14
-
15
17
interface loadtxt
16
- module procedure sloadtxt
17
- module procedure dloadtxt
18
- module procedure qloadtxt
18
+ module procedure loadtxt_sp
19
+ module procedure loadtxt_dp
20
+ module procedure loadtxt_qp
21
+ module procedure loadtxt_int8
22
+ module procedure loadtxt_int16
23
+ module procedure loadtxt_int32
24
+ module procedure loadtxt_int64
19
25
end interface
20
26
21
27
interface savetxt
22
- module procedure ssavetxt
23
- module procedure dsavetxt
24
- module procedure qsavetxt
28
+ module procedure savetxt_sp
29
+ module procedure savetxt_dp
30
+ module procedure savetxt_qp
31
+ module procedure savetxt_int8
32
+ module procedure savetxt_int16
33
+ module procedure savetxt_int32
34
+ module procedure savetxt_int64
25
35
end interface
26
36
27
37
contains
28
38
29
- subroutine sloadtxt (filename , d )
39
+ subroutine loadtxt_sp (filename , d )
30
40
! Loads a 2D array from a text file.
31
41
!
32
42
! Arguments
@@ -68,8 +78,7 @@ subroutine sloadtxt(filename, d)
68
78
end do
69
79
close (s)
70
80
end subroutine
71
-
72
- subroutine dloadtxt (filename , d )
81
+ subroutine loadtxt_dp (filename , d )
73
82
! Loads a 2D array from a text file.
74
83
!
75
84
! Arguments
@@ -111,8 +120,7 @@ subroutine dloadtxt(filename, d)
111
120
end do
112
121
close (s)
113
122
end subroutine
114
-
115
- subroutine qloadtxt (filename , d )
123
+ subroutine loadtxt_qp (filename , d )
116
124
! Loads a 2D array from a text file.
117
125
!
118
126
! Arguments
@@ -154,10 +162,177 @@ subroutine qloadtxt(filename, d)
154
162
end do
155
163
close (s)
156
164
end subroutine
165
+ subroutine loadtxt_int8 (filename , d )
166
+ ! Loads a 2D array from a text file.
167
+ !
168
+ ! Arguments
169
+ ! ---------
170
+ !
171
+ ! Filename to load the array from
172
+ character (len=* ), intent (in ) :: filename
173
+ ! The array 'd' will be automatically allocated with the correct dimensions
174
+ integer (int8), allocatable , intent (out ) :: d(:,:)
175
+ !
176
+ ! Example
177
+ ! -------
178
+ !
179
+ ! integer(int8), allocatable :: data(:, :)
180
+ ! call loadtxt("log.txt", data) ! 'data' will be automatically allocated
181
+ !
182
+ ! Where 'log.txt' contains for example::
183
+ !
184
+ ! 1 2 3
185
+ ! 2 4 6
186
+ ! 8 9 10
187
+ ! 11 12 13
188
+ ! ...
189
+ !
190
+ integer :: s
191
+ integer :: nrow,ncol,i
192
+
193
+ s = open (filename)
194
+
195
+ ! determine number of columns
196
+ ncol = number_of_columns(s)
197
+
198
+ ! determine number or rows
199
+ nrow = number_of_rows_numeric(s)
200
+
201
+ allocate (d(nrow, ncol))
202
+ do i = 1 , nrow
203
+ read (s, * ) d(i, :)
204
+ end do
205
+ close (s)
206
+ end subroutine
207
+ subroutine loadtxt_int16 (filename , d )
208
+ ! Loads a 2D array from a text file.
209
+ !
210
+ ! Arguments
211
+ ! ---------
212
+ !
213
+ ! Filename to load the array from
214
+ character (len=* ), intent (in ) :: filename
215
+ ! The array 'd' will be automatically allocated with the correct dimensions
216
+ integer (int16), allocatable , intent (out ) :: d(:,:)
217
+ !
218
+ ! Example
219
+ ! -------
220
+ !
221
+ ! integer(int16), allocatable :: data(:, :)
222
+ ! call loadtxt("log.txt", data) ! 'data' will be automatically allocated
223
+ !
224
+ ! Where 'log.txt' contains for example::
225
+ !
226
+ ! 1 2 3
227
+ ! 2 4 6
228
+ ! 8 9 10
229
+ ! 11 12 13
230
+ ! ...
231
+ !
232
+ integer :: s
233
+ integer :: nrow,ncol,i
234
+
235
+ s = open (filename)
157
236
237
+ ! determine number of columns
238
+ ncol = number_of_columns(s)
239
+
240
+ ! determine number or rows
241
+ nrow = number_of_rows_numeric(s)
158
242
159
- subroutine ssavetxt (filename , d )
160
- ! Saves a 2D array into a textfile.
243
+ allocate (d(nrow, ncol))
244
+ do i = 1 , nrow
245
+ read (s, * ) d(i, :)
246
+ end do
247
+ close (s)
248
+ end subroutine
249
+ subroutine loadtxt_int32 (filename , d )
250
+ ! Loads a 2D array from a text file.
251
+ !
252
+ ! Arguments
253
+ ! ---------
254
+ !
255
+ ! Filename to load the array from
256
+ character (len=* ), intent (in ) :: filename
257
+ ! The array 'd' will be automatically allocated with the correct dimensions
258
+ integer (int32), allocatable , intent (out ) :: d(:,:)
259
+ !
260
+ ! Example
261
+ ! -------
262
+ !
263
+ ! integer(int32), allocatable :: data(:, :)
264
+ ! call loadtxt("log.txt", data) ! 'data' will be automatically allocated
265
+ !
266
+ ! Where 'log.txt' contains for example::
267
+ !
268
+ ! 1 2 3
269
+ ! 2 4 6
270
+ ! 8 9 10
271
+ ! 11 12 13
272
+ ! ...
273
+ !
274
+ integer :: s
275
+ integer :: nrow,ncol,i
276
+
277
+ s = open (filename)
278
+
279
+ ! determine number of columns
280
+ ncol = number_of_columns(s)
281
+
282
+ ! determine number or rows
283
+ nrow = number_of_rows_numeric(s)
284
+
285
+ allocate (d(nrow, ncol))
286
+ do i = 1 , nrow
287
+ read (s, * ) d(i, :)
288
+ end do
289
+ close (s)
290
+ end subroutine
291
+ subroutine loadtxt_int64 (filename , d )
292
+ ! Loads a 2D array from a text file.
293
+ !
294
+ ! Arguments
295
+ ! ---------
296
+ !
297
+ ! Filename to load the array from
298
+ character (len=* ), intent (in ) :: filename
299
+ ! The array 'd' will be automatically allocated with the correct dimensions
300
+ integer (int64), allocatable , intent (out ) :: d(:,:)
301
+ !
302
+ ! Example
303
+ ! -------
304
+ !
305
+ ! integer(int64), allocatable :: data(:, :)
306
+ ! call loadtxt("log.txt", data) ! 'data' will be automatically allocated
307
+ !
308
+ ! Where 'log.txt' contains for example::
309
+ !
310
+ ! 1 2 3
311
+ ! 2 4 6
312
+ ! 8 9 10
313
+ ! 11 12 13
314
+ ! ...
315
+ !
316
+ integer :: s
317
+ integer :: nrow,ncol,i
318
+
319
+ s = open (filename)
320
+
321
+ ! determine number of columns
322
+ ncol = number_of_columns(s)
323
+
324
+ ! determine number or rows
325
+ nrow = number_of_rows_numeric(s)
326
+
327
+ allocate (d(nrow, ncol))
328
+ do i = 1 , nrow
329
+ read (s, * ) d(i, :)
330
+ end do
331
+ close (s)
332
+ end subroutine
333
+
334
+ subroutine savetxt_sp (filename , d )
335
+ ! Saves a 2D array into a text file.
161
336
!
162
337
! Arguments
163
338
! ---------
@@ -178,9 +353,8 @@ subroutine ssavetxt(filename, d)
178
353
end do
179
354
close (s)
180
355
end subroutine
181
-
182
- subroutine dsavetxt (filename , d )
183
- ! Saves a 2D array into a textfile.
356
+ subroutine savetxt_dp (filename , d )
357
+ ! Saves a 2D array into a text file.
184
358
!
185
359
! Arguments
186
360
! ---------
@@ -201,9 +375,8 @@ subroutine dsavetxt(filename, d)
201
375
end do
202
376
close (s)
203
377
end subroutine
204
-
205
- subroutine qsavetxt (filename , d )
206
- ! Saves a 2D array into a textfile.
378
+ subroutine savetxt_qp (filename , d )
379
+ ! Saves a 2D array into a text file.
207
380
!
208
381
! Arguments
209
382
! ---------
@@ -214,16 +387,101 @@ subroutine qsavetxt(filename, d)
214
387
! Example
215
388
! -------
216
389
!
217
- ! real(dp ) :: data(3, 2)
390
+ ! real(qp ) :: data(3, 2)
218
391
! call savetxt("log.txt", data)
219
392
220
393
integer :: s, i
221
- character (len= 14 ) :: format_string
394
+ s = open (filename, " w" )
395
+ do i = 1 , size (d, 1 )
396
+ write (s, * ) d(i, :)
397
+ end do
398
+ close (s)
399
+ end subroutine
400
+ subroutine savetxt_int8 (filename , d )
401
+ ! Saves a 2D array into a text file.
402
+ !
403
+ ! Arguments
404
+ ! ---------
405
+ !
406
+ character (len=* ), intent (in ) :: filename ! File to save the array to
407
+ integer (int8), intent (in ) :: d(:,:) ! The 2D array to save
408
+ !
409
+ ! Example
410
+ ! -------
411
+ !
412
+ ! integer(int8) :: data(3, 2)
413
+ ! call savetxt("log.txt", data)
414
+
415
+ integer :: s, i
416
+ s = open (filename, " w" )
417
+ do i = 1 , size (d, 1 )
418
+ write (s, * ) d(i, :)
419
+ end do
420
+ close (s)
421
+ end subroutine
422
+ subroutine savetxt_int16 (filename , d )
423
+ ! Saves a 2D array into a text file.
424
+ !
425
+ ! Arguments
426
+ ! ---------
427
+ !
428
+ character (len=* ), intent (in ) :: filename ! File to save the array to
429
+ integer (int16), intent (in ) :: d(:,:) ! The 2D array to save
430
+ !
431
+ ! Example
432
+ ! -------
433
+ !
434
+ ! integer(int16) :: data(3, 2)
435
+ ! call savetxt("log.txt", data)
436
+
437
+ integer :: s, i
438
+ s = open (filename, " w" )
439
+ do i = 1 , size (d, 1 )
440
+ write (s, * ) d(i, :)
441
+ end do
442
+ close (s)
443
+ end subroutine
444
+ subroutine savetxt_int32 (filename , d )
445
+ ! Saves a 2D array into a text file.
446
+ !
447
+ ! Arguments
448
+ ! ---------
449
+ !
450
+ character (len=* ), intent (in ) :: filename ! File to save the array to
451
+ integer (int32), intent (in ) :: d(:,:) ! The 2D array to save
452
+ !
453
+ ! Example
454
+ ! -------
455
+ !
456
+ ! integer(int32) :: data(3, 2)
457
+ ! call savetxt("log.txt", data)
222
458
223
- write (format_string, ' (a1,i06,a7) ' ) ' ( ' , size (d, 2 ), ' f40.34) '
459
+ integer :: s, i
224
460
s = open (filename, " w" )
225
461
do i = 1 , size (d, 1 )
226
- write (s, format_string) d(i, :)
462
+ write (s, * ) d(i, :)
463
+ end do
464
+ close (s)
465
+ end subroutine
466
+ subroutine savetxt_int64 (filename , d )
467
+ ! Saves a 2D array into a text file.
468
+ !
469
+ ! Arguments
470
+ ! ---------
471
+ !
472
+ character (len=* ), intent (in ) :: filename ! File to save the array to
473
+ integer (int64), intent (in ) :: d(:,:) ! The 2D array to save
474
+ !
475
+ ! Example
476
+ ! -------
477
+ !
478
+ ! integer(int64) :: data(3, 2)
479
+ ! call savetxt("log.txt", data)
480
+
481
+ integer :: s, i
482
+ s = open (filename, " w" )
483
+ do i = 1 , size (d, 1 )
484
+ write (s, * ) d(i, :)
227
485
end do
228
486
close (s)
229
487
end subroutine
@@ -289,7 +547,6 @@ integer function open(filename, mode, iostat) result(u)
289
547
character (* ), intent (in ), optional :: mode
290
548
integer , intent (out ), optional :: iostat
291
549
292
- integer :: io_
293
550
character (3 ) :: mode_
294
551
character (:),allocatable :: action_, position_, status_, access_, form_
295
552
0 commit comments