11module stdlib_experimental_io
2- use iso_fortran_env, only: sp= >real32, dp= >real64
2+ use iso_fortran_env, only: sp= >real32, dp= >real64, qp = >real128
33implicit none
44private
55public :: loadtxt, savetxt
66
77interface loadtxt
88 module procedure sloadtxt
99 module procedure dloadtxt
10+ module procedure qloadtxt
1011end interface
1112
1213interface savetxt
1314 module procedure ssavetxt
1415 module procedure dsavetxt
16+ module procedure qsavetxt
1517end interface
1618
1719contains
1820
1921subroutine sloadtxt (filename , d )
22+ ! Loads a 2D array from a text file.
23+ !
24+ ! Arguments
25+ ! ---------
26+ !
27+ ! Filename to load the array from
2028character (len=* ), intent (in ) :: filename
29+ ! The array 'd' will be automatically allocated with the correct dimensions
2130real (sp), allocatable , intent (out ) :: d(:,:)
22- real (dp), allocatable :: tmp(:,:)
23- call dloadtxt(filename, tmp)
24- allocate (d(size (tmp,1 ),size (tmp,2 )))
25- d = real (tmp,sp)
31+ !
32+ ! Example
33+ ! -------
34+ !
35+ ! real(sp), allocatable :: data(:, :)
36+ ! call loadtxt("log.txt", data) ! 'data' will be automatically allocated
37+ !
38+ ! Where 'log.txt' contains for example::
39+ !
40+ ! 1 2 3
41+ ! 2 4 6
42+ ! 8 9 10
43+ ! 11 12 13
44+ ! ...
45+ !
46+ integer :: s
47+ integer :: nrow,ncol,i
48+
49+ open (newunit= s, file= filename, status= " old" )
50+
51+ ! determine number of columns
52+ ncol = number_of_columns(s)
53+
54+ ! determine number or rows
55+ nrow = number_of_rows_numeric(s)
56+
57+ allocate (d(nrow, ncol))
58+ do i = 1 , nrow
59+ read (s, * ) d(i, :)
60+ end do
61+ close (s)
2662end subroutine
2763
2864subroutine dloadtxt (filename , d )
@@ -50,34 +86,59 @@ subroutine dloadtxt(filename, d)
5086! 11 12 13
5187! ...
5288!
53- character :: c
54- integer :: s, ncol, nrow, ios, i
55- logical :: lastwhite
56- real (dp) :: r
89+ integer :: s
90+ integer :: nrow,ncol,i
5791
5892open (newunit= s, file= filename, status= " old" )
5993
6094! determine number of columns
61- ncol = 0
62- lastwhite = .true.
63- do
64- read (s, ' (a)' , advance= ' no' , iostat= ios) c
65- if (ios /= 0 ) exit
66- if (lastwhite .and. .not. whitechar(c)) ncol = ncol + 1
67- lastwhite = whitechar(c)
68- end do
69-
70- rewind(s)
95+ ncol = number_of_columns(s)
7196
7297! determine number or rows
73- nrow = 0
74- do
75- read (s, * , iostat = ios) r
76- if (ios /= 0 ) exit
77- nrow = nrow + 1
98+ nrow = number_of_rows_numeric(s)
99+
100+ allocate (d(nrow, ncol))
101+ do i = 1 , nrow
102+ read (s, * ) d(i, :)
78103end do
104+ close (s)
105+ end subroutine
106+
107+ subroutine qloadtxt (filename , d )
108+ ! Loads a 2D array from a text file.
109+ !
110+ ! Arguments
111+ ! ---------
112+ !
113+ ! Filename to load the array from
114+ character (len=* ), intent (in ) :: filename
115+ ! The array 'd' will be automatically allocated with the correct dimensions
116+ real (qp), allocatable , intent (out ) :: d(:,:)
117+ !
118+ ! Example
119+ ! -------
120+ !
121+ ! real(qp), allocatable :: data(:, :)
122+ ! call loadtxt("log.txt", data) ! 'data' will be automatically allocated
123+ !
124+ ! Where 'log.txt' contains for example::
125+ !
126+ ! 1 2 3
127+ ! 2 4 6
128+ ! 8 9 10
129+ ! 11 12 13
130+ ! ...
131+ !
132+ integer :: s
133+ integer :: nrow,ncol,i
134+
135+ open (newunit= s, file= filename, status= " old" )
79136
80- rewind(s)
137+ ! determine number of columns
138+ ncol = number_of_columns(s)
139+
140+ ! determine number or rows
141+ nrow = number_of_rows_numeric(s)
81142
82143allocate (d(nrow, ncol))
83144do i = 1 , nrow
@@ -86,10 +147,28 @@ subroutine dloadtxt(filename, d)
86147close (s)
87148end subroutine
88149
150+
89151subroutine ssavetxt (filename , d )
90- character (len=* ), intent (in ) :: filename
91- real (sp), intent (in ) :: d(:,:)
92- call dsavetxt(filename, real (d,dp))
152+ ! Saves a 2D array into a textfile.
153+ !
154+ ! Arguments
155+ ! ---------
156+ !
157+ character (len=* ), intent (in ) :: filename ! File to save the array to
158+ real (sp), intent (in ) :: d(:,:) ! The 2D array to save
159+ !
160+ ! Example
161+ ! -------
162+ !
163+ ! real(sp) :: data(3, 2)
164+ ! call savetxt("log.txt", data)
165+
166+ integer :: s, i
167+ open (newunit= s, file= filename, status= " replace" )
168+ do i = 1 , size (d, 1 )
169+ write (s, * ) d(i, :)
170+ end do
171+ close (s)
93172end subroutine
94173
95174subroutine dsavetxt (filename , d )
@@ -115,6 +194,69 @@ subroutine dsavetxt(filename, d)
115194close (s)
116195end subroutine
117196
197+ subroutine qsavetxt (filename , d )
198+ ! Saves a 2D array into a textfile.
199+ !
200+ ! Arguments
201+ ! ---------
202+ !
203+ character (len=* ), intent (in ) :: filename ! File to save the array to
204+ real (qp), intent (in ) :: d(:,:) ! The 2D array to save
205+ !
206+ ! Example
207+ ! -------
208+ !
209+ ! real(dp) :: data(3, 2)
210+ ! call savetxt("log.txt", data)
211+
212+ integer :: s, i
213+ open (newunit= s, file= filename, status= " replace" )
214+ do i = 1 , size (d, 1 )
215+ write (s, * ) d(i, :)
216+ end do
217+ close (s)
218+ end subroutine
219+
220+
221+ integer function number_of_columns (s )
222+ ! determine number of columns
223+ integer ,intent (in ):: s
224+
225+ integer :: ios
226+ character :: c
227+ logical :: lastwhite
228+
229+ rewind(s)
230+ number_of_columns = 0
231+ lastwhite = .true.
232+ do
233+ read (s, ' (a)' , advance= ' no' , iostat= ios) c
234+ if (ios /= 0 ) exit
235+ if (lastwhite .and. .not. whitechar(c)) number_of_columns = number_of_columns + 1
236+ lastwhite = whitechar(c)
237+ end do
238+ rewind(s)
239+
240+ end function
241+
242+ integer function number_of_rows_numeric (s )
243+ ! determine number or rows
244+ integer ,intent (in ):: s
245+ integer :: ios
246+
247+ real :: r
248+
249+ rewind(s)
250+ number_of_rows_numeric = 0
251+ do
252+ read (s, * , iostat= ios) r
253+ if (ios /= 0 ) exit
254+ number_of_rows_numeric = number_of_rows_numeric + 1
255+ end do
256+
257+ rewind(s)
258+
259+ end function
118260
119261logical function whitechar (char ) ! white character
120262! returns .true. if char is space (32) or tab (9), .false. otherwise
0 commit comments