Overwriting current line with position edit descriptor "T"

Hi all, I intended to overwrite the screen output in the same line when I was writing a subroutine for progress bar.

The snippet below works with char(13), i.e. “carriage return”.

program main
    write(6,'(I1,$)') 1
	write(6,'(A,I1,$)') char(13),2
end

The output is “2” (“1” was wiped and replaced by “2” ).

Also, I tried the position edit descriptor “T”, but failed.

program main
	write(6,'(I1,$)') 1
    write(6,'(T1,I1,$)') 2
end

The output is “12”.

However, the code below with single write statement works:

program main
	write(6,'(I1,T1,I1)') 1,2
end	

I have no idea what exactly happened under the hood.

The only possible reason I could think of is that a write statement may output something like a “record”, and each “record” could not be “touched” by position descriptor “T” in another write statement.

Could you please help me explain this?

A write by default produces a record indeed, so the cursor goes to the next line and the next write starts on that one. Try it with ADVANCE= “NO”.

1 Like

Various compilers buffered lines in various ways regarding T field descriptors in the past, but the current standard description states the position is relative to the beginning of the output of the current write statement, so the same result should occur with the example. There were still arguments about what a T field at the end of a format should do (is it skipped as it was not required for output, does it position the beginning of the next write statement, …) but most thought that should not solve it either. There are solutions involving writing into an internal file, using ANSI cursor positioning escape functions, using terminfo and termlib interfaces, calling ncurses/curses libraries, GUI libraries, and graphic libraries but some very nice ones have already been done using basic carriage returns for the most part. Several are buried in large collections but one that stands out as a stand-alone package is GitHub - szaghi/forbear: Fortran (progress) B(e)ar envinronment. It would be nice to perhaps have a list on the Fortran Wiki or in @Beliavsky’s lists if not there already. “forbear” would be a nice fpm(1) package but it predates fpm(1). The github page actually includes an animated gif that should convince you it is a very complete implementation quite quickly.

progress bars on github

github packages including progress bars

2 Likes

Here is a somewhat more standard way of doing this.

program overwr
   write(*,'(i1)',advance='no') 1
   write(*,'(a,i1)') achar(13), 2
end program overwr
1 Like

I’ll just add that the $ edit descriptor is non-standard, though it is widely implemented. @urbanjost is correct that the tab stop for the T edit descriptor is relative to the current WRITE.

2 Likes

Yeah, T being relative to the WRITE statement got cleared up as there was a very good argument that you would have to not write output till a newline and would need an ability to buffer I/O up to at least the length of the limit for formatted I/O lines; but if the arguments about some of the following were resolved I am not sure what the resolution was. But the 890 example below seems to conform to the standard and lets you stay on the same line using multiple writes with each write being able to start in an earlier column, but then it is unclear whether the line is cleared from the starting point, whether you could would get overprinting on a printer, if all devices can “back up”, …
I will bet you still get different output from different compilers with the following; but most compilers did let you start the output at the beginning of the line with the second write in the “890” example at the end. To “T” or not to “T” is the question.

program dusty_corners
! the WRITE statement output is buffered, NOT the line so T edit descriptor
! is relative to the current WRITE output, not the entire line; or output
! would have to wait till the line (possibly of arbitrary length) was
! completely built. That is, not output could occur till a line advance
! at the earliest.
!
!  so, this will produce "12"
   write(*,'(i1)',advance='no') 1
   write(*,'(t1,i1)')  2
!  T and X "positioning for the next output" is a little more confusing

!  since all arguments are written, is t1 even used?
   write(*,'(i1,t1)',advance='no') 3
   write(*,'(i1)')  4

!  do you think 'THIS IS THE END' should be printed or not?
   write(*,'(i1,"THIS IS THE END")') 5
!  but here YES! But once or twice? On one line or two?
   write(*,'(i1,"THIS IS THE END")',advance='no') 6,7
   write(*,*)

!  here, T1 is inarguably used so using escape character should not be needed.
!  So do you get 890, 80, or 0 with your compiler?
   write(*,'(i1,t1,a)',advance='no') 89,''
   write(*,'(i1)')  0
end program dusty_corners

gfortran got this

*12*
34
5THIS IS THE END
6THIS IS THE END
7THIS IS THE END
0

But the last one stayed on the same line as 89 is gone. Also note calling the NEW_LINE(‘A’) function can be used instead of achar(13) in some of the previous examples, which arguably is clearer.

1 Like

In the 54K and lower baud rate days repainting the entire line would have been very slow. It is rather amazing that now-adays using a terminal emulator, not even “real” terminals that you do not even see a flicker; so not the way it would have been done in the past, but this makes a Q&D progress bar, which is a lot easier with modern Fortran and modern computer speeds than it used to be.

module M_progress_bar
implicit none
private
public :: print_progress_bar
contains
subroutine print_progress_bar(progress)
use,intrinsic :: iso_fortran_env, only : stdout=>output_unit
real, intent(in)           :: progress
integer,parameter          :: PB_WIDTH = 60
integer                    :: sofar
   sofar = nint(progress * (PB_WIDTH + 1))
   write(stdout,'(A, " progress: ", F5.1,A)',advance="no") char(13), progress*100, '% '
   write(stdout, "('[',A,']',A)",advance="no") repeat("|",sofar)//repeat(' ',PB_WIDTH-sofar+1),''
   flush(stdout)
end subroutine print_progress_bar
end module M_progress_bar
program testit
use  M_progress_bar, only : print_progress_bar
implicit none
integer :: arbitrary_max, arbitrary_count
real    :: percent, old_percent
arbitrary_max = 333
percent = 0.00
old_percent = -1.00
do arbitrary_count = 1, arbitrary_max
    percent = real(arbitrary_count) / real(arbitrary_max)
    if(old_percent /= percent) call print_progress_bar(percent)
    old_percent=percent
    call execute_command_line('sleep 0.0')
enddo
end program testit
1 Like

Ah, that explains it! :+1:

In most cases these days, I think new_line() returns achar(10), while achar(13) is a different character. The way new_line() is described in the standard, it can also return other character(s) depending on the character kind of the argument and also maybe (I’m unsure) on the filesystem characteristics. For example, when used on a windows filesystem, I think it results in a <cr><lf> sequence in the file, with subsequent items in the write statement, if any, output following that sequence. The standard also mentions connection to a stream file, but it is unclear to me if that is necessary in order for new_line() to be defined. For example, a simple assignment a=new_line('a') is mentioned in the standard, and that obviously has nothing to do with filesystems or file connections. The new_line() intrinsic can also return a space character if there is no corresponding character within the arguments character kind.

The length of the result of the new_line intrinsic is always 1, so it cannot return <cr><lf> (at least for ASCII).

Looks like new_line(‘a’) does not work after all, as you indicated.

Yes I agree, but look at section 16.9.150 in the standard (2023 final draft). The example given there is

WRITE(10,'(A)') 'New'//NEW_LINE('a')//'Line'

When unit 10 is connected to a formatted stream file, this statement is defined to write a record containing “New” and then another record containing “Line”. In order for that to happen on a windows file system (or any other external file system with this kind of multicharacter line termination convention), a <cr><lf> sequence must be inserted into the external file. One assumes that somehow the fortran i/o library combines with the new_line() output to produce this result, but the details of how this happens is not specified by the language standard. If one counts the characters in the external file (say with wc) or looks at the binary contents (say with od), then in one case you would see the one-character sequence and in the other case you would see the two-character sequence.

Look also at section 13.7.4. Here the new_line() function is required to do the same thing as a a slash edit descriptor, which on a windows file system requires that multicharacter line termination convention.

Something else related to this is Table 18.1. Here the constants C_NEW_LINE and C_CARRIAGE_RETURN are defined as single characters of either kind C_CHAR or of default kind. There is a note that specifies new_line(C_NEW_LINE) is C_NEW_LINE.

One might imagine a situation where multiple file systems are available, and one write statement writes to a windows file system and another write statement writes to a posix/unix file system. On the former, the multicharacter sequence would be written, while on the latter the single character <lf> would be written to the external file. I don’t have a windows file system on this computer to test that hypothesis, but I think that is what would happen if I did (and if the fortran compiler supported both file systems).

Also, the standard does not specify what happens when the unit is connected to a normal formatted file (i.e. not opened for stream access). On the computers I use these days, the same thing happens in both cases, they both result in two output records. I think this is an extension, something not specified by the standard. I don’t know what happens on a windows-like file system with a mullticharacter line termination convention in this case, but I’m guessing the same thing will occur.

I don’t think this is an error in the standard, I think it is simply trying the best it can to accommodate multiple file system conventions and also multiple character sets, and this is what we programmers now have to work with.

edit: I was curious what happens with the above write statement when the unit number is replaced with a character array to make it an internal write. The two possibilities are that the whole string is placed into the first element, or that ‘New’ is placed in the first element and ‘Line’ is placed into the second. On two compilers that I tried, they both put everything into the first array element, including the <lf> character between them, and leave the second element unchanged, the same as occurs with a simple assignment into the first array element. If that element is written out (to a file or to the screen), it is then split into two separate lines. I presume this is standard behavior, I didn’t look it up.

I suppose by “file system” you meant “file format” (i.e., “unix” vs “dos”, not “fat/ntfs” vs “ext4/btrfs/apfs”, etc.).

Since the “unix” file format is supported by most applications by default (just not by the ones coming from Microsoft), expecting new_line to behave the way you describe (when on Windows) is a bit of a stretch imho. Maybe @sblionel could clarify.

The slash in a format statement/string might indeed behave in the way you describe it, but that’s compiler-specific.

@urbanjost’s dusty_corners program gave 4 different results with 5 compilers in a Linux Ubuntu system. I don’t have nagfor. All the dates are from the --version output except lfortran’s, which came from Tags · lfortran/lfortran · GitHub. Which (if any) are standard-conforming?
AMD flang 5.0.0 (2024_09_24)

12
4
5THIS IS THE END
6THIS IS THE END7THIS IS THE END
0

ifx 2025.2.0 (20250605) and g95 0.94 (Jan 17 2013)

12
4
5THIS IS THE END
6THIS IS THE END
7THIS IS THE END
0

lfortran 0.54.0 (June 2025)

12
34
5THIS IS THE END
6THIS IS THE END
7THIS IS THE END 
*0

gfortran 15.1.0 (2025)

12
34
5THIS IS THE END
6THIS IS THE END
7THIS IS THE END
0

The standard talks about records but is silent on how the underlying implementation separates records. OpenVMS, for example, supports many on-disk formats, the oldest of which use metadata not visible to the user to indicate the length of each record. You cannot assume any particular character sequence visible to the user.

The standard is very clear on the return value of the NEW_LINE intrinsic - it is ACHAR(10) or CHAR(10,KIND(A)) if that is representable. Only for STREAM output does this have a meaning. If you are on a platform such as Windows where LF is not the record separator for stream output, the implementation must convert that single LF to whatever the appropriate sequence is.

For example, I ran the following program using ifx on Windows:

    open (unit=1,file='test.txt',form='formatted',access='stream')
    write (1,'(*(A))') 'ABC',NEW_LINE('a'),'DEF'
    end

If I look at the file using a binary editor, I see:

41 42 43 0D 0A 44 45 46 0D 0A

in other words, that single LF got turned into CR LF by the ifx runtime library.

What this means is that you can write stream files in a platform-independent fashion and depend on the implementation to do whatever is required to create the indicated records.

1 Like

So, it’s more or less what I was thinking —that there’s no magic involved in the new_line intrinsic, but the compiler’s runtime might do a different interpretation when i/o statements are involved.

I suppose the same conversion does not apply for sequential access, does it?

It does not.

1 Like

Lfortran wins. It should be

12
34
5THIS IS THE END
6THIS IS THE END
7THIS IS THE END
*0

The T descriptor was easier to implement when Fortran formatted output was always record-based and null strings and internal read and writes were not allowed. Going back to that for a moment the T field was only used to position within the record buffer and any further output from subsequent write statements would appear on the next line, not on the line just produced.

Essentially now with all the added possibilities you pretty much have to state that X and T edit descriptors may only appear in sequential advancing I/O or that each WRITE is treated as if it is buffered until a record is generated and the position is always at the end of output generated for non-advancing or stream I/O. That is, T and X are used only for composing the “record” to be produced and not for determing where the output from a subsequent WRITE will begin. Add to that the quirk that reuse of a format produces a new line even if the output is non-advancing or stream (you can use an asterisk for a repeat count to prevent that), and that field overflow should produce asterisks and that a null string has to be treated as output to prevent catch-22 symptoms and all the other ones are presenting a “feature” that causes inconsistencies.

Each behavior can empirically be treated as a “feature” though. That means if you take advantage of the behavior you can do things like position back to the beginning of a line without using escape characters for the next line, and so on. Doing something like a progress bar in particular might inadvertently “use” these dusty corners. Any program behavior, intentional or not, becomes a program feature given enough time, as they say. So rack one up for the new guy (lfortran). It is the first compiler I ever saw get what I consider the right answer and cannot find where the standard says that output is wrong, even though it might take reading between the lines to pick a winner

So one simple statement is that if you change all the advance=‘no’ to advance=‘yes’ you should see all the same characters in the same order in the outout. The only diffeence should be that there are end-of-records produced for every WRITE. No subsequent WRITE should be changing the output of the WRITE before it. Depending on your output device escape characters might produce positioning at locations other than the end of the previous line or the beginning of a new one, but that is outside the scope of Fortran (like what achar(13) or achar(10) or ANSI escape codes might do.

So change.all the ‘no’ to ‘yes’ and ignoring newlines do you have the same characters in the output with any of them except lfortran? The answer should be “yes” or somehing is wrong.

1 Like

Consider the following program:

program newline
   open(10,file='out.txt',access='stream',form='formatted')
   WRITE(10,'(A/A)') 'New', 'Line'
   WRITE(10,'(A)') 'New'//NEW_LINE('a')//'Line'
   close(10)
   open(10,file='out.txt',access='sequential',form='formatted',position='append')
   WRITE(10,'(A/A)') 'New', 'Line'
   WRITE(10,'(A)') 'New'//NEW_LINE('a')//'Line'
end program newline

$ flang newline.f90 && a.out && cat out.txt
New
Line
New
Line
New
Line
New
Line

Section 13.7.4 requires the second two lines to be exactly the same as the first two lines. This should be true regardless of the file system or operating system.

However, if the file is not opened for stream access, as with the last two write statements above, then the standard does not require the third pair of lines to be identical to the last pair. On the machines I’ve tested, they are, but that is not specified, or required, by the standard. I think a compiler would be allowed to put the last two lines above on a single line, or perhaps even generate a run time error if the <lf> is considered to be a nonprinting character or if the line is considered by the compiler to be malformed.

Could someone running on a windows machine please verify this? What happens with the last two write statements?

Steve Lionel already clarified, that the behavior you described is not caused by the new_line intrinsic, but by the compiler’s runtime on i/o statements.

It’s only for (formatted) stream access, though. So it’s less tragic than expected.

(I know it’s supposed to be a feature, but having to deal with those extra “^M” is kind of annoying.)