@@ -9,7 +9,6 @@ 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
1312 use stdlib_optval, only: optval
1413 use stdlib_ascii, only: is_blank
1514 use stdlib_string_type, only : string_type
@@ -147,7 +146,7 @@ contains
147146
148147 if (ios/=0) then
149148 write(msgout,1) trim(iomsg),i,trim(filename)
150- call error_stop(msg= trim(msgout) )
149+ error stop trim(msgout)
151150 end if
152151
153152 end do
@@ -168,7 +167,7 @@ contains
168167
169168 if (ios/=0) then
170169 write(msgout,1) trim(iomsg),i,trim(filename)
171- call error_stop(msg= trim(msgout) )
170+ error stop trim(msgout)
172171 end if
173172
174173 enddo
@@ -179,7 +178,7 @@ contains
179178
180179 if (ios/=0) then
181180 write(msgout,1) trim(iomsg),i,trim(filename)
182- call error_stop(msg= trim(msgout) )
181+ error stop trim(msgout)
183182 end if
184183
185184 enddo
@@ -231,7 +230,7 @@ contains
231230
232231 if (ios/=0) then
233232 write(msgout,1) trim(iomsg),i,trim(filename)
234- call error_stop(msg= trim(msgout) )
233+ error stop trim(msgout)
235234 end if
236235
237236 end do
@@ -367,7 +366,7 @@ contains
367366 position_='asis'
368367 status_='new'
369368 case default
370- call error_stop( "Unsupported mode: "//mode_(1:2) )
369+ error stop "Unsupported mode: "//mode_(1:2)
371370 end select
372371
373372 select case (mode_(3:3))
@@ -376,7 +375,7 @@ contains
376375 case('b')
377376 form_='unformatted'
378377 case default
379- call error_stop( "Unsupported mode: "//mode_(3:3))
378+ error stop "Unsupported mode: "//mode_(3:3)
380379 end select
381380
382381 access_ = 'stream'
@@ -422,9 +421,9 @@ contains
422421 else if (a(i:i) == ' ') then
423422 cycle
424423 else if(any(.not.lfirst)) then
425- call error_stop( "Wrong mode: "//trim(a) )
424+ error stop "Wrong mode: "//trim(a)
426425 else
427- call error_stop( "Wrong character: "//a(i:i) )
426+ error stop "Wrong character: "//a(i:i)
428427 endif
429428 end do
430429
@@ -473,7 +472,7 @@ contains
473472 if (present(iostat)) then
474473 iostat = stat
475474 else if (stat /= 0) then
476- call error_stop( trim(msg))
475+ error stop trim(msg)
477476 end if
478477 end subroutine getline_char
479478
0 commit comments