@@ -120,7 +120,8 @@ contains
120120 !! ...
121121 !!
122122 integer :: s
123- integer :: nrow, ncol, i, skiprows_, max_rows_
123+ integer :: nrow, ncol, i, ios, skiprows_, max_rows_
124+ character(len=128) :: iomsg,msgout
124125
125126 skiprows_ = max(optval(skiprows, 0), 0)
126127 max_rows_ = optval(max_rows, -1)
@@ -142,7 +143,13 @@ contains
142143 allocate(d(max_rows_, ncol))
143144
144145 do i = 1, skiprows_
145- read(s, *)
146+ read(s, *, iostat=ios, iomsg=iomsg)
147+
148+ if (ios/=0) then
149+ write(msgout,1) trim(iomsg),i,trim(filename)
150+ call error_stop(msg=trim(msgout))
151+ end if
152+
146153 end do
147154
148155 ! Default to format used for savetxt if fmt not specified.
@@ -157,16 +164,30 @@ contains
157164 if ( fmt_ == '*' ) then
158165 ! Use list directed read if user has specified fmt='*'
159166 do i = 1, max_rows_
160- read (s,*) d(i, :)
167+ read (s,*,iostat=ios,iomsg=iomsg) d(i, :)
168+
169+ if (ios/=0) then
170+ write(msgout,1) trim(iomsg),i,trim(filename)
171+ call error_stop(msg=trim(msgout))
172+ end if
173+
161174 enddo
162175 else
163176 ! Otherwise pass default or user specified fmt string.
164177 do i = 1, max_rows_
165- read (s,fmt_) d(i, :)
178+ read (s,fmt_,iostat=ios,iomsg=iomsg) d(i, :)
179+
180+ if (ios/=0) then
181+ write(msgout,1) trim(iomsg),i,trim(filename)
182+ call error_stop(msg=trim(msgout))
183+ end if
184+
166185 enddo
167186 endif
168187
169188 close(s)
189+
190+ 1 format('loadtxt: error <',a,'> reading line ',i0,' of ',a,'.')
170191
171192 end subroutine loadtxt_${t1[0]}$${k1}$
172193 #:endfor
@@ -193,20 +214,31 @@ contains
193214 !!```
194215 !!
195216
196- integer :: s, i
217+ integer :: s, i, ios
218+ character(len=128) :: iomsg,msgout
197219 s = open(filename, "w")
198220 do i = 1, size(d, 1)
199221 #:if 'real' in t1
200- write(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",:,1x))") d(i, :)
222+ write(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",:,1x))", &
201223 #:elif 'complex' in t1
202- write(s, "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",:,1x))") d(i, :)
224+ write(s, "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",:,1x))", &
203225 #:elif 'integer' in t1
204- write(s, "(*"//FMT_INT(1:len(FMT_INT)-1)//",:,1x))") d(i, :)
226+ write(s, "(*"//FMT_INT(1:len(FMT_INT)-1)//",:,1x))", &
205227 #:else
206- write(s, *) d(i, :)
228+ write(s, *, &
207229 #:endif
230+ iostat=ios,iomsg=iomsg) d(i, :)
231+
232+ if (ios/=0) then
233+ write(msgout,1) trim(iomsg),i,trim(filename)
234+ call error_stop(msg=trim(msgout))
235+ end if
236+
208237 end do
209238 close(s)
239+
240+ 1 format('savetxt: error <',a,'> writing line ',i0,' of ',a,'.')
241+
210242 end subroutine savetxt_${t1[0]}$${k1}$
211243 #:endfor
212244
0 commit comments