write(*,'(I2)', advance='no')

Im trying to write to stdout and want to write a number, then write over that same number with another number with out advancing the line.

So far no luck. Is this possible?

Character CR
CR = char(13)
 
do ind = 1,5
  write(*, '(i1,i0)',advance='no') ind   ! write a number
  CALL SLEEP(1)
  write(*, '(A1)', advance='no')  CR    !go to start of line
enddo

Nothing shows up on the screen until after the loop. I tried to flush (6) but still no luck.

1 Like

I guess if you want to use flush(6) you have to use write(6, ). This seems to work for me.

program overwrite
character :: cr
integer :: ind

cr = char(13)

do ind = 1, 5
   write(6, '(i0)', advance='no') ind   ! write a number
   flush(6)
   call sleep(1)
   write(*, '(a1)', advance='no') cr    ! go to start of line
enddo

endprogram
2 Likes

Depends on your compiler and your OS to some extent. Note that the LUN * and 6 are not always the same unit, which might explain why the flush did not work, and some compilers cache a line being built with advance=‘no’, and some compilers have a funny idea about whether using the T descriptor should act on an entire line or the last WRITE. You can get a lot fancier if your terminal supports ANSI in-line escape sequences and query the cursor position and then position the cursor before each write, but that requires raw I/O mode which usually requires calling very platform-specific C routines; and you can usually get it to work using stream I/O but there is no standard way to open stdout as a stream so that takes some fooling around, and so on. So let’s just hope it is that * and 6 are not the same unit. If this does not work you have to identify what system type you are on and what compiler you are using, and possibly what terminal emulator you are using:

use, intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
character,parameter :: cr = char(13)
do ind = 15,0,-1
   write(stdout, '(i2)',advance='no') ind  ! write a number
   flush(stdout)
   call sleep(1)
   write(stdout, '(a1)', advance='no')  cr    ! go to start of line
   flush(stdout)
enddo
end program overwrite

also note SLEEP(3f) is not a standard function, but a very common extension.

Looks like I duplicated an answer. Did not type fast enough! Did dig up and simplify an old example that basically does the same thing that worked with a couple of different compilers …

program demo_percent_done
use, intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
implicit none
integer :: i, nr=10 
   do i=1,nr 
      call percent_done(real(i),real(nr))
      call sleep(1)  !give a delay in seconds 
   enddo 
   write(stdout,'(a)')
contains

!> place a non-advancing status counter on terminal display (not when redirected to a file! See extension ISATTY(3f))
subroutine percent_done(part,whole)
real,intent(in) :: part,whole
   write(stdout,fmt="(a1,' Percent Complete: ',t21,f0.2,'%')",ADVANCE="NO") achar(13), (part/whole)*100.0
   flush(stdout)
end subroutine percent_done

end program demo_percent_done
2 Likes

That worked with intels compiler on BBC a windows 10 machine. Thanks

The following works, but then I realized it is almost identical to the solutions posted by @urbanjost @implicitall.

But aside from this, note that the flush() statement does not necessarily lead to printing the output on screen. To enforce a print on screen, one could use a trick like call execute_command_line(" ") (the credit for it goes to @rouson, a developer of OpenCoarrays).

program writeOnTheSameLine

    !use ifport
    use iso_fortran_env, only: output_unit
    integer :: ind
    character(len=1), parameter :: CARRIAGE_RETURN = achar(13)

    do ind = 1, 50000
      write(output_unit, '(1a1,1i5)',advance='no') CARRIAGE_RETURN, ind ! rewrite a number
      flush(output_unit)
      !call sleep(1)
    end do

end program writeOnTheSameLine
2 Likes

It’s also possible to import the C_CARRIAGE_RETURN defined in ISO_C_BINDING:

  use, intrinsic :: iso_c_binding, only: C_CARRIAGE_RETURN
...
      write(output_unit, '(1a1,1i5)',advance='no') C_CARRIAGE_RETURN, ind ! rewrite a number

or:

  use, intrinsic :: iso_c_binding, only: CR => C_CARRIAGE_RETURN
...
      write(output_unit, '(1a1,1i5)',advance='no') CR, ind ! rewrite a number
1 Like