Skip to content

Commit

Permalink
Revert "call error_stop -> error stop" (#894)
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz authored Nov 23, 2024
2 parents f6d317e + 5cbeb2b commit 68524b3
Showing 1 changed file with 10 additions and 9 deletions.
19 changes: 10 additions & 9 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module stdlib_io
use, intrinsic :: iso_fortran_env, only : input_unit
use stdlib_kinds, only: sp, dp, xdp, qp, &
int8, int16, int32, int64
use stdlib_error, only: error_stop
use stdlib_optval, only: optval
use stdlib_ascii, only: is_blank
use stdlib_string_type, only : string_type
Expand Down Expand Up @@ -146,7 +147,7 @@ contains

if (ios/=0) then
write(msgout,1) trim(iomsg),i,trim(filename)
error stop trim(msgout)
call error_stop(msg=trim(msgout))
end if

end do
Expand All @@ -167,7 +168,7 @@ contains

if (ios/=0) then
write(msgout,1) trim(iomsg),i,trim(filename)
error stop trim(msgout)
call error_stop(msg=trim(msgout))
end if

enddo
Expand All @@ -178,7 +179,7 @@ contains

if (ios/=0) then
write(msgout,1) trim(iomsg),i,trim(filename)
error stop trim(msgout)
call error_stop(msg=trim(msgout))
end if

enddo
Expand Down Expand Up @@ -230,7 +231,7 @@ contains

if (ios/=0) then
write(msgout,1) trim(iomsg),i,trim(filename)
error stop trim(msgout)
call error_stop(msg=trim(msgout))
end if

end do
Expand Down Expand Up @@ -366,7 +367,7 @@ contains
position_='asis'
status_='new'
case default
error stop "Unsupported mode: "//mode_(1:2)
call error_stop("Unsupported mode: "//mode_(1:2))
end select

select case (mode_(3:3))
Expand All @@ -375,7 +376,7 @@ contains
case('b')
form_='unformatted'
case default
error stop "Unsupported mode: "//mode_(3:3)
call error_stop("Unsupported mode: "//mode_(3:3))
end select

access_ = 'stream'
Expand Down Expand Up @@ -421,9 +422,9 @@ contains
else if (a(i:i) == ' ') then
cycle
else if(any(.not.lfirst)) then
error stop "Wrong mode: "//trim(a)
call error_stop("Wrong mode: "//trim(a))
else
error stop "Wrong character: "//a(i:i)
call error_stop("Wrong character: "//a(i:i))
endif
end do

Expand Down Expand Up @@ -472,7 +473,7 @@ contains
if (present(iostat)) then
iostat = stat
else if (stat /= 0) then
error stop trim(msg)
call error_stop(trim(msg))
end if
end subroutine getline_char

Expand Down

0 comments on commit 68524b3

Please sign in to comment.