Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit 36031fc

Browse files
committed
underscore
1 parent 462d908 commit 36031fc

File tree

7 files changed

+82
-82
lines changed

7 files changed

+82
-82
lines changed

‎doc/specs/stdlib_io.md‎

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -205,7 +205,7 @@ Provides a npy file called `filename` that contains the rank-2 `array`.
205205
{!example/io/example_savenpy.f90!}
206206
```
207207

208-
## `getline`
208+
## `get_line`
209209

210210
### Status
211211

@@ -217,9 +217,9 @@ Read a whole line from a formatted unit into a string variable
217217

218218
### Syntax
219219

220-
`call ` [[stdlib_io(module):getline(interface)]] ` (unit, line[, iostat][, iomsg])`
220+
`call ` [[stdlib_io(module):get_line(interface)]] ` (unit, line[, iostat][, iomsg])`
221221

222-
`call ` [[stdlib_io(module):getline(interface)]] ` (line[, iostat][, iomsg])`
222+
`call ` [[stdlib_io(module):get_line(interface)]] ` (line[, iostat][, iomsg])`
223223

224224
### Arguments
225225

@@ -241,7 +241,7 @@ Read a whole line from a formatted unit into a string variable
241241
### Example
242242

243243
```fortran
244-
{!example/io/example_getline.f90!}
244+
{!example/io/example_get_line.f90!}
245245
```
246246

247247
## Formatting constants
@@ -261,7 +261,7 @@ Provides formats for all kinds as defined in the `stdlib_kinds` module.
261261
{!example/io/example_fmt_constants.f90!}
262262
```
263263

264-
## `getfile` - Read a whole ASCII file into a `character` or a `string` variable
264+
## `get_file` - Read a whole ASCII file into a `character` or a `string` variable
265265

266266
### Status
267267

@@ -274,7 +274,7 @@ The function provides an optional error-handling mechanism via the `state_type`
274274

275275
### Syntax
276276

277-
`call [[stdlib_io(module):getfile(subroutine)]] (filename, file [, err] [, delete=.false.])`
277+
`call [[stdlib_io(module):get_file(subroutine)]] (filename, file [, err] [, delete=.false.])`
278278

279279
### Class
280280
Function
@@ -299,5 +299,5 @@ Exceptions trigger an `error stop` unless the optional `err` argument is provide
299299
### Example
300300

301301
```fortran
302-
{!example/io/example_getfile.f90!}
302+
{!example/io/example_get_file.f90!}
303303
```

‎example/io/CMakeLists.txt‎

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
ADD_EXAMPLE(fmt_constants)
2-
#ADD_EXAMPLE(getline)
3-
ADD_EXAMPLE(getfile)
2+
#ADD_EXAMPLE(get_line)
3+
ADD_EXAMPLE(get_file)
44
ADD_EXAMPLE(loadnpy)
55
ADD_EXAMPLE(loadtxt)
66
ADD_EXAMPLE(open)
Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
1-
! Demonstrate usage of `getfile`
2-
program example_getfile
3-
use stdlib_io, only: getfile
1+
! Demonstrate usage of `get_file`
2+
program example_get_file
3+
use stdlib_io, only: get_file
44
use stdlib_string_type, only: string_type
55
use stdlib_error, only: state_type
66
implicit none
@@ -10,11 +10,11 @@ program example_getfile
1010
type(state_type) :: err
1111

1212
! Read a file into a string
13-
call getfile(filename, filecontent, err=err)
13+
call get_file(filename, filecontent, err=err)
1414

1515
if (err%error()) then
1616
print *, err%print()
1717
else
1818
print *, "Success! File "//filename//" imported."
1919
end if
20-
end program example_getfile
20+
end program example_get_file
Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,13 @@
11
program example_getline
22
use, intrinsic :: iso_fortran_env, only: input_unit, output_unit
3-
use stdlib_io, only: getline
3+
use stdlib_io, only: get_line
44
implicit none
55
character(len=:), allocatable :: line
66
integer :: stat
77

8-
call getline(input_unit, line, stat)
8+
call get_line(input_unit, line, stat)
99
do while (stat == 0)
1010
write (output_unit, '(a)') line
11-
call getline(input_unit, line, stat)
11+
call get_line(input_unit, line, stat)
1212
end do
1313
end program example_getline

‎src/stdlib_io.fypp‎

Lines changed: 35 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -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

668668
end module stdlib_io

‎test/io/CMakeLists.txt‎

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ ADDTEST(savetxt_qp)
1313
set_tests_properties(loadtxt_qp PROPERTIES LABELS quadruple_precision)
1414
set_tests_properties(savetxt_qp PROPERTIES LABELS quadruple_precision)
1515

16-
ADDTEST(getline)
16+
ADDTEST(get_line)
1717
ADDTEST(npy)
1818
ADDTEST(open)
1919
ADDTEST(parse_mode)

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /