stdlib icon indicating copy to clipboard operation
stdlib copied to clipboard

Input() function

Open ivan-pi opened this issue 5 years ago • 17 comments

Is there any interest to have a Python-like input() function?

Effectively, this would be a convenience function for the following pattern:

    write(output_unit,'(A)',advance='no') 'Enter a value: '
    read(input_unit,'(A)') buffer
    str = trim(buffer)

the purpose of which is to collect some user input together with a friendly prompt message. The Fortran interface could be something like:

  impure function input(prompt,stat) result(str)
    character(len=*), intent(in), optional :: prompt
      !! Text that is displayed as a prompt.
    integer, intent(out), optional :: stat
      !! Status flag used to raise an exception.
    character(len=:), allocatable :: str
  end function

In Python 2 they used to have two versions, input and raw_input. The first would try to evaluate the input argument and return it with the correct type, while raw_input would return a string. In Python 3 raw_input was removed and input returns a string. The user must then explicitly use eval or a type-conversion routine like int or float to get the desired value.

One issue I don't know how to deal with yet in Fortran are trailing whitespaces. The Python function preserves trailing whitespaces:

>>> s = input('Enter a value: ')
Enter a value:     4     
>>> s
'    4    '

To achieve this in Fortran it might be necessary to interface with C.

ivan-pi avatar Dec 06 '20 18:12 ivan-pi

I think this would be helpful. A small utility function, useful in small quick programs for interacting with the user.

On Sun, Dec 6, 2020, at 11:48 AM, Ivan Pribec wrote:

Is there any interest to have a Python-like input() https://docs.python.org/3/library/functions.html#input function?

Effectively, this would be a convenience function for the following pattern:

write(output_unit,'(A)',advance='no') 'Enter a value: '
read(input_unit,'(A)') buffer
str = trim(buffer)

the purpose of which is to collect some user input together with a friendly prompt message. The Fortran interface could be something like:

impure function input(prompt,stat) result(str) character(len=*), intent(in), optional :: prompt !! Text that is displayed as a prompt. integer, intent(out), optional :: stat !! Status flag used to raise an exception. character(len=:), allocatable :: str end function In Python 2 they used to have two versions, input and raw_input. The first would try to evaluate the input argument and return it with the correct type, while raw_input would return a string. In Python 3 raw_input was removed and input returns a string. The user must then explicitly use eval or a type-conversion routine like int or float to get the desired value.

One issue I don't know how to deal with yet in Fortran are trailing whitespaces. The Python function preserves trailing whitespaces:

`>>> s = input('Enter a value: ') Enter a value: 4

s ' 4 ' ` To achieve this in Fortran it might be necessary to interface with C.

— You are receiving this because you are subscribed to this thread. Reply to this email directly, view it on GitHub https://github.com/fortran-lang/stdlib/issues/259, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWCVWMVHGN7RFV5OPQLSTPGYDANCNFSM4UPQPNGQ.

certik avatar Dec 06 '20 19:12 certik

I find this pattern used often in "beginner" programs, e.g.

radius = str2real(input("Enter a radius: "))
print *, "Area of circle: ", radius*pi**2
end

But like you suggest for quick interactive programs, before you are able to build a full-fledged CLI, it can also come handy. Having string-to-numerical type conversions routines is required to make this useful.

I found a solution in Fortran, that appears to work correctly with trailing whitespaces and even tabs: https://stackoverflow.com/questions/50680306/how-can-i-know-the-length-of-user-input-with-trailing-whitespaces-in-fortran The trick is to read the string one character at a time.

ivan-pi avatar Dec 07 '20 13:12 ivan-pi

:+1: I think this would be a great addition, especially for beginners as you say, and tutorials.

milancurcic avatar Dec 07 '20 14:12 milancurcic

I agree with others: I think input() would be a great addition! Should it go in stdlib_io?

jvdp1 avatar Dec 07 '20 14:12 jvdp1

I think stdlib_io is a suitable place for it.

On Mon, 7 Dec 2020 at 15:57, Jeremie Vandenplas [email protected] wrote:

I agree with others: I think input() would be a great addition! Should it go in stdlib_io?

— You are receiving this because you authored the thread. Reply to this email directly, view it on GitHub https://github.com/fortran-lang/stdlib/issues/259#issuecomment-739970105, or unsubscribe https://github.com/notifications/unsubscribe-auth/AFA33S7G3XB33JSXJQDJDQ3STTUN5ANCNFSM4UPQPNGQ .

ivan-pi avatar Dec 07 '20 15:12 ivan-pi

I think stdlib_io is the only suitable place for it. :)

milancurcic avatar Dec 07 '20 15:12 milancurcic

Let's do it!

On Mon, Dec 7, 2020, at 8:17 AM, Milan Curcic wrote:

I think stdlib_io is the only suitable place for it. :)

— You are receiving this because you commented. Reply to this email directly, view it on GitHub https://github.com/fortran-lang/stdlib/issues/259#issuecomment-739982272, or unsubscribe https://github.com/notifications/unsubscribe-auth/AAAFAWGGHSKOZKJHJIOUG2TSTTWZLANCNFSM4UPQPNGQ.

certik avatar Dec 07 '20 15:12 certik

I found a solution in Fortran, that appears to work correctly with trailing whitespaces and even tabs: https://stackoverflow.com/questions/50680306/how-can-i-know-the-length-of-user-input-with-trailing-whitespaces-in-fortran The trick is to read the string one character at a time.

It might be worth having a look also at John Burkardt's filum.f90 (LGPL). In particular, subroutines s_to_i4, s_to_r8, s_to_r8vec, etc.. are relevant here (although others might be very useful for stdlib in general). They need modernisation but I found them to be pretty robust.

epagone avatar Dec 07 '20 21:12 epagone

I have a similar routine called rd() that has significant trailing spaces and returns a string by default, but if given an optional numeric value returns a value of that type in a module called M_io.f90 that is part of the GPF (General Purpose Fortran) files, but was extracted

git clone https://github.com/urbanjost/M_io

that might further the discussion. the text for the manpage reads

NAME
rd(3f) - [M_io] ask for string from standard input with user-definable prompt
(LICENSE:PD)

  function rd(prompt,default) result(strout)

   character(len=*),intent(in)              :: prompt

   character(len=*),intent(in)              :: default
         or
   integer,intent(in)                       :: default
         or
   real,intent(in)                          :: default
         or
   doubleprecision,intent(in)               :: default

   character(len=:),allocatable,intent(out) :: strout

DESCRIPTION
   Ask for string or value from standard input with user-definable prompt
   up to 20 times.

       Do not use the function in an I/O statement as not all versions of
       Fortran support this form of recursion. Numeric values may be input in
       standard INTEGER, REAL, and DOUBLEPRECISION formats or as whole numbers
       in base 2 to 36 in the format BASE#VALUE.

OPTIONS
       prompt Prompt string; displayed on same line as input is read from

       default
              default answer on carriage-return. The type of the default     
             determines the type of the output.

RETURNS
       strout returned string or value. If an end-of-file or system error is
              encountered the string "EOF" is returned, or a "Nan" numeric
              value.

EXAMPLE
       Sample program:

          program demo_rd
          use M_io, only : rd
          character(len=:),allocatable :: mystring
          doubleprecision              :: d
          real                         :: r
          integer                      :: i

          INFINITE: do
             mystring=rd('Enter string or "STOP":',default='Today')
             if(mystring.eq.'STOP')stop
             i=rd('Enter integer:',default=huge(0))
             r=rd('Enter real:',default=huge(0.0))
             d=rd('Enter double:',default=huge(0.0d0))

             write(*,*)'I=', i, 'R=', r, 'D=',d,  'MYSTRING=', mystring
          enddo INFINITE

          end program demo_rd

AUTHOR
       John S. Urban, 1993

LICENSE
       Public Domain

              determines the type of the output.


urbanjost avatar Dec 08 '20 01:12 urbanjost

PS: If you change getline to read_line it handles tabs, and is available as a fpm package. There are a lot of related routines in GPF

If I would suggest a change it would be that it allow multiple values as well, allowing for a default seperator of space and comma for numbers and with strings you could argue, but would probably have to be an argument passed in but I still use , a lot so you can entr something like green,red by default. Another variant I have allows for a block of help text to be displayed if you enter "?" as the value and never takes a blank string or the string ? which is a little less general just for an idea to discuss but it is not available on-line.

urbanjost avatar Dec 08 '20 01:12 urbanjost

I did not mean my reference to my similar routine to end discussion here. I thought it might serve as an example on how trailing spaces and returning non-string types and the idea of a default might be worth discussing. Seems like everything stopped after the post of the rd() function when I was hoping to further it. I also like having an option to color the prompt using ANSI escape sequences but not all terminal (emulators) support that. I think not having a retry like mine is probably better handled by returning an error; if not putting a limit on retries like mine does is recommended as you can otherwiseinadvertently cause a program to enter an infinite loop when input is not coming from interactive input.

urbanjost avatar Dec 11 '20 03:12 urbanjost

@urbanjost no worries at all. Would you be interested in sending a PR with code + specs for the input() function? I think we all agree that would be helpful, now we just need to nail down the specifics.

certik avatar Dec 11 '20 03:12 certik

Thanks, but I can't at this time. I made a small fpm package with a seed anyone pursuing this is welcome to use with no restrictions.

It is the subdirectory in miscellaneous under the directory M_input. It contains an input(3f) function as close to the description as I could manage with the time I have available.

git clone  https://github.com/urbanjost/miscellaneous
cd miscellaneous/M_input
fpm run 

If you use "fpm run --compiler NAME" you will find it is never as simple as it seems if you enter ctrl-D at the prompt for a number or enter a huge integer string like

11111111111111111111111111111111111111111111111111111111111111111111111

you will find ifort, nvfortran, and gfortran all handle it differently. It should handle Inf and NaN more robustly, but I have seen other parts of stdlib that should be able to handle that so I did not duplicate it here. It would be useful if a version of stdlib was available as a simple fpm(1) package.

Hope it is helpful, but I have to opt out on this one. Having had a routine like this for a long time I find I use it mostly in a quick prototype; but I use the getline(3f) routine that it uses a lot, actually.

urbanjost avatar Dec 11 '20 22:12 urbanjost

Deleting the example github repository, so thought I would put a copy of the alpha version here for anyone interested in the future.

module M_input
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stderr=>error_unit
implicit none
private
public :: getline
public :: input
integer,parameter,private :: dp=kind(0.0d0)
interface input
   module procedure rd_character
   module procedure rd_integer
   module procedure rd_real
   module procedure rd_dp
end interface input
contains
!>NAME
!>   getline(3f) - [M_input] read line from specified LUN into allocatable string
!>                 up to line length limit
!>   (LICENSE:PD)
!>
!>SYNTAX
!>  function getline(line,lun) result(ier)
!>
!>   character(len=:),allocatable,intent(out) :: line
!>   integer,intent(in),optional              :: lun
!>   integer,intent(out)                      :: ier
!>
!>DESCRIPTION
!>   Read a line of any length up to programming environment maximum
!>   line length. Requires Fortran 2003+.
!>
!>   It is primarily expected to be used when reading input which will
!>   then be parsed.
!>
!>   The input file must have a PAD attribute of YES for the function
!>   to work properly, which is typically true.
!>
!>   The simple use of a loop that repeatedly re-allocates a character
!>   variable in addition to reading the input file one buffer at a
!>   time could (depending on the programming environment used) be
!>   inefficient, as it could reallocate and allocate memory used for
!>   the output string with each buffer read.
!>
!>OPTIONS
!>   LINE   line read. Trailing spaces are significant.
!>   LUN    optional LUN (Fortran logical I/O unit) number. Defaults
!>          to stdin.
!>RETURNS
!>   IER    zero unless an error occurred. If not zero, LINE returns the
!>          I/O error message.
!>
!>EXAMPLE
!>  Sample program:
!>
!>   program demo_getline
!>   use,intrinsic :: iso_fortran_env, only : stdin=>input_unit
!>   use M_input, only : getline
!>   implicit none
!>   character(len=:),allocatable :: line
!>      open(unit=stdin,pad='yes')
!>      INFINITE: do while (getline(line)==0)
!>         write(*,'(a)')'['//line//']'
!>      enddo INFINITE
!>      if(is_iostat_end(ier))stop 'end of file'
!>      write(*,'(*(g0))')'<ERROR>ended on ',trim(line)
!>   end program demo_getline
!>
!>LICENSE
!>   MIT License

function getline(line,lun) result(ier)
implicit none

!>> getline(3f): read line from LUN into allocatable string up to length limit

character(len=:),allocatable,intent(out) :: line
integer,intent(in),optional              :: lun
integer                                  :: ier
character(len=256)                       :: message

integer,parameter                        :: buflen=1024
character(len=:),allocatable             :: line_local
character(len=buflen)                    :: buffer
integer                                  :: isize
integer                                  :: lun_local

   line_local=''
   ier=0
   if(present(lun))then
      lun_local=lun
   else
      lun_local=stdin
   endif
   open(lun_local,pad='yes')

   INFINITE: do
   ! read characters from line and append to result
      message=''
      read(lun_local,iostat=ier,fmt='(a)',advance='no',size=isize,&
      & iomsg=message) buffer
      ! read next buffer (might use stream I/O for files

      ! other than stdin so system line limit is not limiting
      if(isize.gt.0)line_local=line_local//buffer(:isize)
      ! append what was read to result
      if(is_iostat_eor(ier))then
      !if hit EOR reading is complete unless backslash ends the line
         ier=0
         ! hitting end of record is not an error for this routine
         exit INFINITE
         ! end of reading line
     elseif(ier.ne.0)then
     ! end of file or error
        line=trim(message)
        exit INFINITE
     endif
   enddo INFINITE
   line=line_local
end function getline

!>NAME
!>input(3f) - [M_input] ask for string from standard input with
!>            user-definable prompt
!>(LICENSE:PD)
!>
!>  function input(prompt,default) result(strout)
!>
!>   character(len=*),intent(in)              :: prompt
!>
!>   Any one of

!>    character(len=*),intent(in),optional     :: default
!>    integer,intent(in),optional              :: default
!>    real,intent(in),optional                 :: default
!>    integer,parameter                        :: dp=kind(0.0d0)
!>    real(kind==dp),intent(in),optional       :: default
!>
!>   character(len=:),allocatable,intent(out) :: strout
!>
!>DESCRIPTION
!>   Ask for string or value from standard input with user-definable prompt
!>
!>   Do not use the function in an I/O statement as not all versions of
!>   Fortran support this form of recursion. Numeric values may be input
!>   in standard INTEGER, REAL, and DOUBLEPRECISION formats.
!>
!>OPTIONS
!>   prompt    Prompt string; displayed on same line as input is read from
!>   default   default answer on carriage-return. The type of the default
!>             determines the type of the output.
!>RETURNS
!>   strout    returned string or value. If an end-of-file or system error
!>             is encountered the null character is returned when returning
!>             a string, or a "Nan" numeric value for REAL values or
!>             HUGE(0) for an INTEGER.
!>EXAMPLE
!>  Sample program:
!>
!>   program demo_input
!>   use M_input, only : input
!>   character(len=:),allocatable :: mystring
!>   integer,parameter,private :: dp=kind(0.0d0)
!>   real(kind=dp)                :: d
!>   real                         :: r
!>   integer                      :: i
!>
!>   INFINITE: do
!>      mystring=input('Enter string or "STOP":',default='Today')
!>      if(mystring.eq.'STOP')stop
!>      i=input('Enter integer:',default=huge(0))
!>      r=input('Enter real:',default=huge(0.0))
!>      d=input('Enter double:',default=huge(0.0d0))
!>
!>      write(*,'(*(g0))')'I=',i,' R=',r,' D=',d,' MYSTRING=',mystring
!>   enddo INFINITE
!>
!>   end program demo_input
!>
!>LICENSE
!>   MIT License

function rd_character(prompt,default,iostat) result(strout)
implicit none

!>> rd_character(3fp): ask for string with user-definable prompt

character(len=*),intent(in)           :: prompt
character(len=*),intent(in),optional  :: default
integer,optional,intent(out)          :: iostat
character(len=:),allocatable          :: strout

integer                               :: len_prompt
integer                               :: iostat_local
!>*!integer                               :: idum

   len_prompt=len(prompt)
   iostat_local=0

   if(len_prompt.gt.0)then
      write(*,'(a)',advance='no')prompt
   else
      write(*,'("Enter value>")',advance='no')prompt
   endif
   iostat_local=getline(strout,stdin)
   if(iostat_local.ne.0)then
      !*!attempt to work-around nvfortran and gfortran bug|unexpected feature
      !*! once a ctrl-D |EOF is encountered gfortran|nvfortran do not allow subsequent reads
      !*!if(is_iostat_end(iostat_local))rewind(stdin,iostat=idum)
      !*!if(is_iostat_end(iostat_local))open(stdin,pad='yes')
      if(is_iostat_end(iostat_local))backspace stdin
      strout=char(0)
   elseif(present(default).and.strout.eq.'')then
      strout=default
   endif
   if(present(iostat))iostat=iostat_local
end function rd_character

function nan()
character(len=3),save :: nanstring='NaN'
real(kind=dp) :: nan
   read(nanstring,*)nan
end function nan

function rd_dp(prompt,default,iostat) result(dvalue)
implicit none

!>> rd_dp(3fp): ask for DOUBLE number with user-definable prompt

real(kind=dp)                         :: dvalue
character(len=*),intent(in)           :: prompt
real(kind=dp),intent(in)              :: default
integer,intent(out),optional          :: iostat

character(len=:),allocatable          :: strout
character(len=256)                    :: message
integer                               :: iostat_local

   iostat_local=0
   strout=rd_character(prompt,iostat=iostat_local)
   if(iostat_local.ne.0)then
      write(*,'(*(g0))')'<ERROR>*input* failed to read from stdin:',strout
      dvalue=nan()
   elseif(strout.eq.'')then
      dvalue=default
   else
      read(strout,*,iostat=iostat_local,iomsg=message)dvalue
      if(iostat_local.ne.0)then
            write(stderr,'(*(g0))') &
            & '<ERROR>*input* input ['//strout//'] failed as a number:', &
            & trim(message)
            dvalue=nan()
      endif
   endif
   if(present(iostat))iostat=iostat_local
end function rd_dp

function rd_real(prompt,default,iostat) result(rvalue)
implicit none
!>> rd_real(3fp): ask for REAL number input with user-definable prompt
real                         :: rvalue
real(kind=dp)                :: dvalue
character(len=*),intent(in)  :: prompt
real,intent(in)              :: default
integer,intent(out),optional :: iostat
   !*! what about Nan, Inf, -Inf? Likely place for compiler bugs
   dvalue=rd_dp(prompt,dble(default),iostat)
   if(dvalue.ne.dvalue)then
      write(stderr,'(*(g0))') &
      & '<ERROR>*input* value [',dvalue,'] is indefinite'
      rvalue=huge(0.0)
   else
      rvalue=real(dvalue)
   endif
end function rd_real

function rd_integer(prompt,default,iostat) result(ivalue)
implicit none
!>> rd_integer(3fp): ask for INTEGER number with user-definable prompt
integer                      :: ivalue
real(kind=dp)                :: dvalue
character(len=*),intent(in)  :: prompt
integer,intent(in)           :: default
integer,intent(out),optional :: iostat
   dvalue=rd_dp(prompt,dble(default),iostat)
   !*! what about Nan, Inf, -Inf?
   if(dvalue.ne.dvalue)then
      write(stderr,'(*(g0))') &
      & '<ERROR>*input* value [',dvalue,'] is indefinite'
      ivalue=huge(0)
   elseif(dvalue.gt.huge(0))then
      write(stderr,'(*(g0))') &
      & '<ERROR>*input* value [',dvalue,'] greater than ', huge(0)
      ivalue=huge(0)
   elseif(dvalue.lt.1-huge(0))then
      write(stderr,'(*(g0))') &
      & '<ERROR>*input* value [',dvalue,'] less than ', 1-huge(0)
      ivalue=1-huge(0)
   else
      ivalue=nint(dvalue)
   endif
end function rd_integer

end module M_input

urbanjost avatar Jan 10 '21 21:01 urbanjost

heyy, Can i work on this issue, if no one is working on this one?? Please assign it to me

Brijesh-Thakkar avatar Dec 05 '25 11:12 Brijesh-Thakkar

Thank you @Brijesh-Thakkar for your interest. I am not aware of someone working on this . So feel free to open a PR with some suggestions.

jvdp1 avatar Dec 07 '25 15:12 jvdp1