How to read from stdin directly?

read *, allows us to read from stdin. But I am not looking for that.

Is there any way to read what user has entered through terminal without using read *,?
read *, must have been implemented by reading from stdin. I am looking for the method read *, has used to read from stdin because I am trying to create a read *, function of my own.

How can I access that input stream (stdin) to read characters in it one by one OR all at a time if reading one by one is not possible?

Moreover, it will be helpful for me if someone can suggest me some good articles, blogs or something else on read *, which are easy to understand for a beginner? Thank you!

Gfortran has

FGET — Read a single character in stream mode from stdin

Description :

Read a single character in stream mode from stdin by bypassing normal formatted output. Stream I/O should not be mixed with normal record-oriented (formatted or unformatted) I/O on the same unit; the results are unpredictable.

This intrinsic is provided in both subroutine and function forms; however, only one form can be used in any given program unit.

Note that the FGET intrinsic is provided for backwards compatibility with g77 . GNU Fortran provides the Fortran 2003 Stream facility. Programmers should consider the use of new stream IO feature in new code for future portability. See also Fortran 2003 status.

Does this mean that the functionality of FGET is available in a stanrdard fashion by reading from INPUT_UNIT when opened as a stream? (Just wondering, I have never tried it)

.Unfortunately reading pre-connected units as a stream is not portable. It is also unreliable to mix C I/O with Fortran I/O. Some compilers have little or no issues with this, but others do. So you can call the C functions to do stream I/O but if you do that do not also rely on Fortran I/O on the same file to work reliably. Stream I/O works nicely with regular files. See the links in

for starters concerning why stream I/O is not supported for creating filters in a simple portable manner by Fortran.

1 Like

If you wanted, you could write a C function that reads from stdin using getc and call that from Fortran. Or you could READ(INPUT_UNIT,*) where INPUT_UNIT is a named constant defined in iso_fortran_env. There were some old operating systems (RT-11 from DEC comes to mind) where terminal input went to a known address in memory that you could read directly in assembly language. However, on modern systems, the connection between stdin and your terminal is a complicated process in the OS and not accessible to normal programmers. In general, any READ or WRITE statement is going to involved at least one, and usually multiple, layers of OS code. Trying to circumvent that would be a huge waste of time and result in highly non-portable code.

Clive Page has a small section about reading single keystrokes on Unix platforms (search for “Reading single keystrokes from Fortran” near the bottom of the page).

The approach used is to call functions in the header <termios.h> that provides a general terminal interface to control asynchronous communications ports.

Click for details

:warning:

I do not hold the license to the following code, and have included it only for demonstration purposes. The code itself is a modified version of the file sys_keyin.c from Clive Page.

/* sys_keyin.c  This version works on _most_ Unix platforms
  Fortran calls:
      CALL SYS_KEYSET(1)   to set single-keystroke mode
      CALL SYS_KEYIN(KEY)  to get integer ASCII code for next key-stroke
                           e.g. 32 for space, 97 for "a" etc.
                           (Integer rather than character to cope with
                           control characters etc.)
      CALL SYS_KEYSET(0)   to restore normal input mode
  Author:  Clive Page,  cgp@le.ac.uk, 1994-JUL-13
*/

#include <stdio.h>
#include <termios.h>
void sys_keyset_(int *mode)
{
  static struct termios termattr,saveattr;
  static tcflag_t save_flags;

  if(*mode != 0)
  {
    tcgetattr(0,&termattr);
    saveattr=termattr;
    termattr.c_lflag&=~(ICANON);
    termattr.c_lflag&=~(ECHO);
    termattr.c_cc[VMIN] = 1;
    termattr.c_cc[VTIME] = 0;
    tcsetattr(0,TCSADRAIN,&termattr);
  }
  else
  {
    tcsetattr(0,TCSADRAIN,&saveattr);
  }
}


void sys_keyin_(int *nextch)
{
  *nextch = getchar();
}

Use of the module from Fortran would look like:

module sys_key

  use iso_c_binding, only: c_int

  implicit none
  public

  integer(c_int), parameter :: SYS_KEYMODE_NORMAL = 0
  integer(c_int), parameter :: SYS_KEYMODE_SINGLE = 1

  interface
    subroutine sys_keyset(mode) bind(c,name="sys_keyset_")
      import c_int
      integer(c_int), intent(in) :: mode
    end subroutine
    subroutine sys_keyin(nextch) bind(c,name="sys_keyin_")
      import c_int
      integer(c_int), intent(in) :: nextch
    end subroutine
  end interface

end module

program main

  use sys_key

  implicit none

  integer(c_int), parameter :: ESC = 27_c_int

  integer(c_int) :: nextch

  write(*,*) "Press ESC to exit..."

  call sys_keyset(SYS_KEYMODE_SINGLE)

  do
    call sys_keyin(nextch)
    write(*,*) "The key pressed was: "//achar(nextch), nextch
    if (nextch == ESC) exit
  end do

  !
  ! Don't forget to set the mode back to normal
  ! or your terminal will remain in the wrong mode
  !
  call sys_keyset(SYS_KEYMODE_NORMAL)

end program

Small demonstration:

~/fortran/sys_keyin$ gcc -c sys_keyin.c 
~/fortran/sys_keyin$ gfortran sys_keyin.o sys_key.f90
~/fortran/sys_keyin$ ./a.out
 Press ESC to exit...
 The key pressed was: 1          49
 The key pressed was: 2          50
 The key pressed was: 3          51
 The key pressed was: a          97
 The key pressed was: b          98
 The key pressed was: c          99
 The key pressed was: >          62
 The key pressed was: <          60
 The key pressed was: =          61
 The key pressed was:            32
 The key pressed was: 
          10
 The key pressed was: q         113
 The key pressed was: e          27

For fun try pressing some control characters or localized (non-ASCII) letter characters on your keyboard (in my case I have čćšž).

1 Like

On Unix-like operating system, you can furthermore call stty through the execute_command_line() routine to enable the cbreak mode of the terminal:

! example.f90
program main
    use, intrinsic :: iso_c_binding, only: c_int
    implicit none

    interface
        function c_getchar() bind(c, name='getchar')
            import :: c_int
            integer(kind=c_int) :: c_getchar
        end function c_getchar
    end interface

    integer :: ch

    ! Enable cbreak mode.
    call execute_command_line('stty -echo cbreak </dev/tty >/dev/tty 2>&1')

    print '(a)', 'Press <q> to quit.'

    do
        ch = c_getchar()
        print '(a, i0)', 'Key pressed: ', ch
        if (ch == ichar('q')) exit
    end do

    ! Disable cbreak mode.
    call execute_command_line('stty echo -cbreak </dev/tty >/dev/tty 2>&1')
end program main

If you want to output the pressed key, simply remove the -echo argument.

Build and run the example with, for instance:

$ gfortran -o example example.f90
$ ./example
Press <q> to quit.
Key pressed: 70
2 Likes

First of all, stdin is not a defined entity/concept within the Fortran language. It may be available in compilers such as Gfortran that are closely coupled to a C compiler, since stdin, stdout, stderr, etc., are part of STDIO.

Secondly, if your Fortran routines access one or more of these files directly and also through C routines indirectly, the order in which characters are read/written to the file may be unpredictable.

1 Like