@@ -626,8 +626,68 @@ function unix_path(path) result(nixpath)
626
626
627
627
end function unix_path
628
628
629
-
630
- ! > read a line of arbitrary length into a CHARACTER variable from the specified LUN
629
+ ! >AUTHOR: fpm(1) contributors
630
+ ! !LICENSE: MIT
631
+ ! >
632
+ ! !##NAME
633
+ ! ! getline(3f) - [M_io:READ] read a line of arbintrary length from specified
634
+ ! ! LUN into allocatable string (up to system line length limit)
635
+ ! ! (LICENSE:PD)
636
+ ! !
637
+ ! !##SYNTAX
638
+ ! ! subroutine getline(unit,line,iostat,iomsg)
639
+ ! !
640
+ ! ! integer,intent(in) :: unit
641
+ ! ! character(len=:),allocatable,intent(out) :: line
642
+ ! ! integer,intent(out) :: iostat
643
+ ! ! character(len=:), allocatable, optional :: iomsg
644
+ ! !
645
+ ! !##DESCRIPTION
646
+ ! ! Read a line of any length up to programming environment maximum
647
+ ! ! line length. Requires Fortran 2003+.
648
+ ! !
649
+ ! ! It is primarily expected to be used when reading input which will
650
+ ! ! then be parsed or echoed.
651
+ ! !
652
+ ! ! The input file must have a PAD attribute of YES for the function
653
+ ! ! to work properly, which is typically true.
654
+ ! !
655
+ ! ! The simple use of a loop that repeatedly re-allocates a character
656
+ ! ! variable in addition to reading the input file one buffer at a
657
+ ! ! time could (depending on the programming environment used) be
658
+ ! ! inefficient, as it could reallocate and allocate memory used for
659
+ ! ! the output string with each buffer read.
660
+ ! !
661
+ ! !##OPTIONS
662
+ ! ! LINE The line read when IOSTAT returns as zero.
663
+ ! ! LUN LUN (Fortran logical I/O unit) number of file open and ready
664
+ ! ! to read.
665
+ ! ! IOSTAT status returned by READ(IOSTAT=IOS). If not zero, an error
666
+ ! ! occurred or an end-of-file or end-of-record was encountered.
667
+ ! ! IOMSG error message returned by system when IOSTAT is not zero.
668
+ ! !
669
+ ! !##EXAMPLE
670
+ ! !
671
+ ! ! Sample program:
672
+ ! !
673
+ ! ! program demo_getline
674
+ ! ! use,intrinsic :: iso_fortran_env, only : stdin=>input_unit
675
+ ! ! use,intrinsic :: iso_fortran_env, only : iostat_end
676
+ ! ! use M_filesystem, only : getline
677
+ ! ! implicit none
678
+ ! ! integer :: iostat
679
+ ! ! character(len=:),allocatable :: line, iomsg
680
+ ! ! open(unit=stdin,pad='yes')
681
+ ! ! INFINITE: do
682
+ ! ! call getline(stdin,line,iostat=iostat,iomsg)
683
+ ! ! if(iostat /= 0) exit INFINITE
684
+ ! ! write(*,'(a)')'['//line//']'
685
+ ! ! enddo INFINITE
686
+ ! ! if(iostat /= iostat_end)then
687
+ ! ! write(*,*)'error reading input:',iomsg
688
+ ! ! endif
689
+ ! ! end program demo_getline
690
+ ! !
631
691
subroutine getline (unit , line , iostat , iomsg )
632
692
633
693
! > Formatted IO unit
@@ -642,12 +702,13 @@ subroutine getline(unit, line, iostat, iomsg)
642
702
! > Error message
643
703
character (len= :), allocatable , optional :: iomsg
644
704
645
- integer , parameter :: FILENAME_MAX = 4096
646
- character (len= FILENAME_MAX) :: buffer
647
- character (len= FILENAME_MAX) :: msg
705
+ integer , parameter :: BUFFER_SIZE = 32768
706
+ character (len= BUFFER_SIZE) :: buffer
707
+ character (len= 256 ) :: msg
648
708
integer :: size
649
709
integer :: stat
650
710
711
+
651
712
allocate (character (len= 0 ) :: line)
652
713
do
653
714
read (unit, ' (a)' , advance= ' no' , iostat= stat, iomsg= msg, size= size) &
0 commit comments