@@ -16,12 +16,12 @@ module stdlib_io
1616 implicit none
1717 private
1818 ! Public API
19- public :: loadtxt, savetxt, open, getline, getfile
19+ public :: loadtxt, savetxt, open, get_line, get_file
2020
2121 !! version: experimental
2222 !!
2323 !! Reads a whole ASCII file and loads its contents into a string variable.
24- !! ([Specification](../page/specs/stdlib_io.html#getfile -read-a-whole-ascii-file-into-a-character-or-a-string-variable))
24+ !! ([Specification](../page/specs/stdlib_io.html#get-file -read-a-whole-ascii-file-into-a-character-or-a-string-variable))
2525 !!
2626 !!### Summary
2727 !! Subroutine interface for reading the content of a file into a string.
@@ -35,10 +35,10 @@ module stdlib_io
3535 !!@note Handles errors using the library's `state_type` error-handling class. If not provided,
3636 !! exceptions will trigger an `error stop`.
3737 !!
38- interface getfile
39- module procedure :: getfile_char
40- module procedure :: getfile_string
41- end interface getfile
38+ interface get_file
39+ module procedure :: get_file_char
40+ module procedure :: get_file_string
41+ end interface get_file
4242
4343 ! Private API that is exposed so that we can test it in tests
4444 public :: parse_mode
@@ -73,12 +73,12 @@ module stdlib_io
7373 !> Version: experimental
7474 !>
7575 !> Read a whole line from a formatted unit into a string variable
76- interface getline
77- module procedure :: getline_char
78- module procedure :: getline_string
79- module procedure :: getline_input_char
80- module procedure :: getline_input_string
81- end interface getline
76+ interface get_line
77+ module procedure :: get_line_char
78+ module procedure :: get_line_string
79+ module procedure :: get_line_input_char
80+ module procedure :: get_line_input_string
81+ end interface get_line
8282
8383 interface loadtxt
8484 !! version: experimental
@@ -287,7 +287,7 @@ contains
287287 number_of_columns = 0
288288
289289 ! Read first non-skipped line as a whole
290- call getline (s, line, ios)
290+ call get_line (s, line, ios)
291291 if (ios/=0 .or. .not.allocated(line)) return
292292
293293 lastblank = .true.
@@ -459,7 +459,7 @@ contains
459459 !> Version: experimental
460460 !>
461461 !> Read a whole line from a formatted unit into a deferred length character variable
462- subroutine getline_char (unit, line, iostat, iomsg)
462+ subroutine get_line_char (unit, line, iostat, iomsg)
463463 !> Formatted IO unit
464464 integer, intent(in) :: unit
465465 !> Line to read
@@ -501,12 +501,12 @@ contains
501501 else if (stat /= 0) then
502502 call error_stop(trim(msg))
503503 end if
504- end subroutine getline_char
504+ end subroutine get_line_char
505505
506506 !> Version: experimental
507507 !>
508508 !> Read a whole line from a formatted unit into a string variable
509- subroutine getline_string (unit, line, iostat, iomsg)
509+ subroutine get_line_string (unit, line, iostat, iomsg)
510510 !> Formatted IO unit
511511 integer, intent(in) :: unit
512512 !> Line to read
@@ -518,43 +518,43 @@ contains
518518
519519 character(len=:), allocatable :: buffer
520520
521- call getline (unit, buffer, iostat, iomsg)
521+ call get_line (unit, buffer, iostat, iomsg)
522522 line = string_type(buffer)
523- end subroutine getline_string
523+ end subroutine get_line_string
524524
525525 !> Version: experimental
526526 !>
527527 !> Read a whole line from the standard input into a deferred length character variable
528- subroutine getline_input_char (line, iostat, iomsg)
528+ subroutine get_line_input_char (line, iostat, iomsg)
529529 !> Line to read
530530 character(len=:), allocatable, intent(out) :: line
531531 !> Status of operation
532532 integer, intent(out), optional :: iostat
533533 !> Error message
534534 character(len=:), allocatable, optional :: iomsg
535535
536- call getline (input_unit, line, iostat, iomsg)
537- end subroutine getline_input_char
536+ call get_line (input_unit, line, iostat, iomsg)
537+ end subroutine get_line_input_char
538538
539539 !> Version: experimental
540540 !>
541541 !> Read a whole line from the standard input into a string variable
542- subroutine getline_input_string (line, iostat, iomsg)
542+ subroutine get_line_input_string (line, iostat, iomsg)
543543 !> Line to read
544544 type(string_type), intent(out) :: line
545545 !> Status of operation
546546 integer, intent(out), optional :: iostat
547547 !> Error message
548548 character(len=:), allocatable, optional :: iomsg
549549
550- call getline (input_unit, line, iostat, iomsg)
551- end subroutine getline_input_string
550+ call get_line (input_unit, line, iostat, iomsg)
551+ end subroutine get_line_input_string
552552
553553 !> Version: experimental
554554 !>
555555 !> Reads a whole ASCII file and loads its contents into a string variable.
556556 !> The function handles error states and optionally deletes the file after reading.
557- subroutine getfile_string (filename,file,err,delete)
557+ subroutine get_file_string (filename,file,err,delete)
558558 !> Input file name
559559 character(*), intent(in) :: filename
560560 !> Output string variable
@@ -568,16 +568,16 @@ contains
568568 character(len=:), allocatable :: filestring
569569
570570 ! Process output
571- call getfile_char (filename,filestring,err,delete)
571+ call get_file_char (filename,filestring,err,delete)
572572 call move(from=fileString,to=file)
573573
574- end subroutine getfile_string
574+ end subroutine get_file_string
575575
576576 !> Version: experimental
577577 !>
578578 !> Reads a whole ASCII file and loads its contents into an allocatable `character` variable.
579579 !> The function handles error states and optionally deletes the file after reading.
580- subroutine getfile_char (filename,file,err,delete)
580+ subroutine get_file_char (filename,file,err,delete)
581581 !> Input file name
582582 character(*), intent(in) :: filename
583583 !> Output string variable
@@ -605,7 +605,7 @@ contains
605605 inquire(file=filename, exist=is_present)
606606 if (.not.is_present) then
607607 allocate(character(len=0) :: file)
608- err0 = state_type('getfile ',STDLIB_IO_ERROR,'File not present:',filename)
608+ err0 = state_type('get_file ',STDLIB_IO_ERROR,'File not present:',filename)
609609 call err0%handle(err)
610610 return
611611 end if
@@ -616,7 +616,7 @@ contains
616616 invalid_size: if (file_size<0) then
617617
618618 allocate(character(len=0) :: file)
619- err0 = state_type('getfile ',STDLIB_IO_ERROR,filename,'has invalid size=',file_size)
619+ err0 = state_type('get_file ',STDLIB_IO_ERROR,filename,'has invalid size=',file_size)
620620 call err0%handle(err)
621621 return
622622
@@ -629,7 +629,7 @@ contains
629629
630630 if (iostat/=0) then
631631 allocate(character(len=0) :: file)
632- err0 = state_type('getfile ',STDLIB_IO_ERROR,'Cannot open',filename,'for read:',iomsg)
632+ err0 = state_type('get_file ',STDLIB_IO_ERROR,'Cannot open',filename,'for read:',iomsg)
633633 call err0%handle(err)
634634 return
635635 end if
@@ -644,7 +644,7 @@ contains
644644 if (iostat/=0) then
645645
646646 inquire(unit=lun,pos=errpos)
647- err0 = state_type('getfile ',STDLIB_IO_ERROR,iomsg,'(',filename,'at byte',errpos,')')
647+ err0 = state_type('get_file ',STDLIB_IO_ERROR,iomsg,'(',filename,'at byte',errpos,')')
648648 call err0%handle(err)
649649 return
650650
@@ -654,15 +654,15 @@ contains
654654
655655 if (want_deleted) then
656656 close(lun,iostat=iostat,status='delete')
657- if (iostat/=0) err0 = state_type('getfile ',STDLIB_IO_ERROR,'Cannot delete',filename,'after reading')
657+ if (iostat/=0) err0 = state_type('get_file ',STDLIB_IO_ERROR,'Cannot delete',filename,'after reading')
658658 else
659659 close(lun,iostat=iostat)
660- if (iostat/=0) err0 = state_type('getfile ',STDLIB_IO_ERROR,'Cannot close',filename,'after reading')
660+ if (iostat/=0) err0 = state_type('get_file ',STDLIB_IO_ERROR,'Cannot close',filename,'after reading')
661661 endif
662662
663663 ! Process output
664664 call err0%handle(err)
665665
666- end subroutine getfile_char
666+ end subroutine get_file_char
667667
668668end module stdlib_io
0 commit comments