Skip to content

Commit 68524b3

Browse files
authored
Revert "call error_stop -> error stop" (#894)
2 parents f6d317e + 5cbeb2b commit 68524b3

File tree

1 file changed

+10
-9
lines changed

1 file changed

+10
-9
lines changed

src/stdlib_io.fypp

+10-9
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ module stdlib_io
99
use, intrinsic :: iso_fortran_env, only : input_unit
1010
use stdlib_kinds, only: sp, dp, xdp, qp, &
1111
int8, int16, int32, int64
12+
use stdlib_error, only: error_stop
1213
use stdlib_optval, only: optval
1314
use stdlib_ascii, only: is_blank
1415
use stdlib_string_type, only : string_type
@@ -146,7 +147,7 @@ contains
146147

147148
if (ios/=0) then
148149
write(msgout,1) trim(iomsg),i,trim(filename)
149-
error stop trim(msgout)
150+
call error_stop(msg=trim(msgout))
150151
end if
151152

152153
end do
@@ -167,7 +168,7 @@ contains
167168

168169
if (ios/=0) then
169170
write(msgout,1) trim(iomsg),i,trim(filename)
170-
error stop trim(msgout)
171+
call error_stop(msg=trim(msgout))
171172
end if
172173

173174
enddo
@@ -178,7 +179,7 @@ contains
178179

179180
if (ios/=0) then
180181
write(msgout,1) trim(iomsg),i,trim(filename)
181-
error stop trim(msgout)
182+
call error_stop(msg=trim(msgout))
182183
end if
183184

184185
enddo
@@ -230,7 +231,7 @@ contains
230231

231232
if (ios/=0) then
232233
write(msgout,1) trim(iomsg),i,trim(filename)
233-
error stop trim(msgout)
234+
call error_stop(msg=trim(msgout))
234235
end if
235236

236237
end do
@@ -366,7 +367,7 @@ contains
366367
position_='asis'
367368
status_='new'
368369
case default
369-
error stop "Unsupported mode: "//mode_(1:2)
370+
call error_stop("Unsupported mode: "//mode_(1:2))
370371
end select
371372

372373
select case (mode_(3:3))
@@ -375,7 +376,7 @@ contains
375376
case('b')
376377
form_='unformatted'
377378
case default
378-
error stop "Unsupported mode: "//mode_(3:3)
379+
call error_stop("Unsupported mode: "//mode_(3:3))
379380
end select
380381

381382
access_ = 'stream'
@@ -421,9 +422,9 @@ contains
421422
else if (a(i:i) == ' ') then
422423
cycle
423424
else if(any(.not.lfirst)) then
424-
error stop "Wrong mode: "//trim(a)
425+
call error_stop("Wrong mode: "//trim(a))
425426
else
426-
error stop "Wrong character: "//a(i:i)
427+
call error_stop("Wrong character: "//a(i:i))
427428
endif
428429
end do
429430

@@ -472,7 +473,7 @@ contains
472473
if (present(iostat)) then
473474
iostat = stat
474475
else if (stat /= 0) then
475-
error stop trim(msg)
476+
call error_stop(trim(msg))
476477
end if
477478
end subroutine getline_char
478479

0 commit comments

Comments
 (0)