@@ -2,6 +2,7 @@ module stdlib_experimental_io
22use stdlib_experimental_kinds, only: sp, dp, qp
33use stdlib_experimental_error, only: error_stop
44use stdlib_experimental_optval, only: optval
5+ use stdlib_experimental_ascii, only: is_blank
56implicit none
67private
78! Public API
@@ -231,16 +232,16 @@ integer function number_of_columns(s)
231232
232233 integer :: ios
233234 character :: c
234- logical :: lastwhite
235+ logical :: lastblank
235236
236237 rewind(s)
237238 number_of_columns = 0
238- lastwhite = .true.
239+ lastblank = .true.
239240 do
240241 read (s, ' (a)' , advance= ' no' , iostat= ios) c
241242 if (ios /= 0 ) exit
242- if (lastwhite .and. .not. whitechar (c)) number_of_columns = number_of_columns + 1
243- lastwhite = whitechar (c)
243+ if (lastblank .and. .not. is_blank (c)) number_of_columns = number_of_columns + 1
244+ lastblank = is_blank (c)
244245 end do
245246 rewind(s)
246247
@@ -265,17 +266,7 @@ integer function number_of_rows_numeric(s)
265266
266267end function
267268
268- pure logical function whitechar(char) ! white character
269- ! returns .true. if char is space (32) or tab (9), .false. otherwise
270- character , intent (in ) :: char
271- if (iachar (char) == 32 .or. iachar (char) == 9 ) then
272- whitechar = .true.
273- else
274- whitechar = .false.
275- end if
276- end function
277-
278- integer function open (filename , mode ) result(u)
269+ integer function open (filename , mode , iostat ) result(u)
279270! Open a file
280271!
281272! To open a file to read:
@@ -293,8 +284,10 @@ integer function open(filename, mode) result(u)
293284
294285character (* ), intent (in ) :: filename
295286character (* ), intent (in ), optional :: mode
296- integer :: io
297- character (3 ):: mode_
287+ integer , intent (out ), optional :: iostat
288+
289+ integer :: io_
290+ character (3 ) :: mode_
298291character (:),allocatable :: action_, position_, status_, access_, form_
299292
300293
@@ -348,37 +341,51 @@ integer function open(filename, mode) result(u)
348341 call error_stop(" Unsupported mode: " // mode_(3 :3 ))
349342end select
350343
351- open (newunit= u, file= filename, &
352- action = action_, position = position_, status = status_, &
353- access = access_, form = form_, &
354- iostat = io)
344+ if (present (iostat)) then
345+ open (newunit= u, file= filename, &
346+ action = action_, position = position_, status = status_, &
347+ access = access_, form = form_, &
348+ iostat = iostat)
349+ else
350+ open (newunit= u, file= filename, &
351+ action = action_, position = position_, status = status_, &
352+ access = access_, form = form_)
353+ end if
355354
356355end function
357356
358357character (3 ) function parse_mode(mode) result(mode_)
359358character (* ), intent (in ) :: mode
360359
361- integer :: i
362- character (:),allocatable :: a
360+ integer :: i
361+ character (:),allocatable :: a
362+ logical :: lfirst(3 )
363363
364364mode_ = ' r t'
365365
366366if (len_trim (mode) == 0 ) return
367367a= trim (adjustl (mode))
368368
369+ lfirst = .true.
369370do i= 1 ,len (a)
370- select case (a(i:i))
371- case (' r' , ' w' , ' a' , ' x' )
371+ if (lfirst(1 ) &
372+ .and. (a(i:i) == ' r' .or. a(i:i) == ' w' .or. a(i:i) == ' a' .or. a(i:i) == ' x' ) &
373+ ) then
372374 mode_(1 :1 ) = a(i:i)
373- case (' +' )
375+ lfirst(1 )= .false.
376+ else if (lfirst(2 ) .and. a(i:i) == ' +' ) then
374377 mode_(2 :2 ) = a(i:i)
375- case (' t' , ' b' )
378+ lfirst(2 )= .false.
379+ else if (lfirst(3 ) .and. (a(i:i) == ' t' .or. a(i:i) == ' b' )) then
376380 mode_(3 :3 ) = a(i:i)
377- case (' ' )
378- cycle
379- case default
381+ lfirst(3 )= .false.
382+ else if (a(i:i) == ' ' ) then
383+ cycle
384+ else if (any (.not. lfirst)) then
385+ call error_stop(" Wrong mode: " // trim (a))
386+ else
380387 call error_stop(" Wrong character: " // a(i:i))
381- end select
388+ endif
382389end do
383390
384391end function
0 commit comments