Stdout buffer in gfortran

Actually I tried FLUSH, CALL FLUSH and neither seemed to work.

Knew that was a possibility, hoped it was not the case though. Having to call C to do a complete flush to a device (or closing and opening the file which is an ugly work-around with some compilers) would be nice in circumstances like the ASCII Donut program.

1 Like

As soon as I say “I wish Fortran had good feature x support like other compiled languages”, I immediately hear “Fortran wasn’t meant to do that”. Sometimes feature x is decent string handling. I get the same answer. Well, at some point, Fortran wasn’t even meant to be typed digitally. I don’t see them furiously punching cards, do I?

I don’t understand why people don’t understand humans communicate in strings, not real(kind=8) or something else. Strings are integral for any type of programming.

“Fortran wasn’t meant to do that” is a great excuse for so many weird, non-conventional behaviors. It seems stupid to call other languages for trivial stuff like this. With the headache of type conversion between c-type and fortran-type, not using fortran all together might seem like a better option somewhere.

On the other hand, I have spent a very productive amount of time rewriting code from other languages in Fortran that have produced huge benefits. I haven’t met a language I could not complain about. But I also would prefer a few changes to Fortran to take down that wall preventing it from being considered general-purpose. I miss the days when I could write anything at all from system utilities to graphics and GUIs with just Fortran on highly-extended Fortran implementations such as on VMS. Fortran used to own graphics; the first relational database I used was in Fortran (RIM0) and so on. If just a few of those capabilities are provided in stdlib I personally would rarely need any other language. REALLY intrigued by how easy it might be to create graphics and GUIs in a browser from a Fortran APP using WASM. I have wanted something like that for all languages (I once thought that was exactly what would come from Netscape); the browser is a ridiculously common and powerful platform if that works out. Did not see it coming though. Might be limiting for large memory apps but that combination might be a big step forward, even with some of the limitations a sandboxed environment introduces. Sure eliminates a lot of packaging and distribution problems.

1 Like

PS: In regards to another recent discussion along the lines of the movie tag “There can be only one” this is one of the cases where having multiple compilers where you can pick one that addresses your issues if another one fails, or try GPUs with one with relative ease when in another that would be nothing but frustrating. So it is nice to see different solutions from different compilers and to compare their pros and cons in a relatively short time. That is one of the up-sides of having multiple compilers. Think how hard it might be to look at the pros and cons of different buffering methodologies without different implementations.

1 Like

Exactly, if fortran wasn’t designed to be general purpose, what’s the reason for modern fortran to be not able to do some stuff general purpose languages can. Learning and using fortran can help in better visualization of control flow, since it is one of the very fewer languages which isn’t ‘inspired’ by c in syntax.

Can you provide link of any compiler comparisons, if any?

I had just used gfortran 99% of the time, thinking there wouldn’t be much difference. It’s time for me to explore other compilers.

Don’t have one handy, but there are several floating around. nvfortran is probably best free one for exploring NVIDIA GPUs; NAG is well-know for trapping programming errors but is $; ifort is know for a plethora of tuning options and auxiliary development tools and I have generally found 20% faster on average than gfortran but others have found the opposite; ifort has what I consider the strongest support for MPI, especially when mixing it with OpenMP; CRAY is the mother of coarrays to mention just a few (sorry if I left out someones favorite … not an exhaustive list).

Speaking of alternative compilers, even with the default buffering of nvfortran and ifort note that writing to /dev/null saves space more than time even with those:

 gfortran x1.f90
+ gfortran x1.f90
time ./a.out >/dev/null
+ ./a.out

real    3m2.712s
user    2m8.677s
sys     0m54.027s
time ./a.out >x.
+ ./a.out

real    1m46.760s
user    1m46.250s
sys     0m0.408s

ifort x1.f90
+ ifort x1.f90
time ./a.out >/dev/null
+ ./a.out

real    1m57.211s
user    1m55.933s
sys     0m1.268s
time ./a.out >x.
+ ./a.out

real    2m9.865s
user    1m57.392s
sys     0m12.372s

nvfortran x1.f90
+ nvfortran x1.f90
time ./a.out >/dev/null
+ ./a.out

real    1m41.245s
user    1m41.190s
sys     0m0.028s
time ./a.out >x.
+ ./a.out

real    1m42.082s 
user    1m41.438s
sys     0m0.404s

and a lot more time is spent in the ASCII processing than you might expect.
I can get the same file with

 time ./a.out >x-

real    0m16.671s
user    0m4.530s
sys     0m11.816s
(test1) urbanjs@venus:~$ cat x2.f90
program test
implicit none
integer :: i, j
do j=1,10000000
      WRITE(*,'("123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ")')
enddo
end program test

a lot faster, although still slow compared to just the write time something like “cp x- x2-”
would give you as a lower bound.

Sort of amazing how much there is to explore in a program less than ten lines long; considering I just initially meant to mention writing to /dev/null was probably an unexpected cause of the worst of what you were seeing, which certainly would be non-intuitive.d

If it were a real-world problem we could get that down more, that is just to point out the cost of ASCII processing.

By the way, the fpm(1) page points to several string-related modules; and there is a good list of resources on the Fortran Wiki; @Beliavsky’s list; and in the online Modern Fortran (not to be confused with a publication of that name) for starters

and several string-related routines are already in stdlib at Fortran-Lang already. Make sure your favorites make it there. Some of the things you are wishing for are already out there, and tools like fpm(1) are making them as accessible as modules in other languages as well.

One thing sometimes forgotten with all the languages out there is there really is only one on any given platform (well, almost), and all these languages are just abstractions for different ways to talk to the same machine. So using some of these tools if you don’t see it in the language you can add it so the next guy just sees it as readily available. After all, a lot of languages are really quite small, it is often what modules/libraries are readily available that adds to their usefulness,

1 Like

Fortran was never meant to be interactive and was never meant to be a systems programming language. Its primary purpose was to describe mathematical computations and to do it expressively, reliably and fast.

Its I/O is geared towards batch operation: data will be read in, the CPU will crunch for hours and the results will be printed, maybe once maybe frequently enough to restart the program if the hardware failed on the way.

It has no concept of address so it cannot be made to control hardware in between I/O.

The only time that you can predict the value of variables is when I/O takes place. Between I/O, all bets are off. The only guarantee is that Output will be as if the described computations had taken place. Interactivity means that programs are sometimes expected to have their internal state inspected by some other program, which interprets the values in some region of memory as an image, say. Doing this in Fortran might not work without doing I/O or marking the variables as VOLATILE.

There’s a place for a systems programming language like C (to write kernels, compilers and browsers), a place for an interactive language like Python (to orchestrate a diversity of tools) and a place for a pure computation number-crunching myriad-core language like Fortran.

3 Likes

I agree with most of your post.

I would say that Fortran was meant to be a language for numerical (array oriented) scientific computing. Easy to program by domain scientists and so on.

However, Fortran has been evolving to adapt for the scientific needs. For example it has added parallelism to the language.

I would argue that modern scientific research development is now predominantly done in Python, Matlab or Julia, all of which are interactive. And so Fortran should also be interactive, because that is what most people in these communities (myself included) expect.

The good news is that almost any language can be made interactive, including Fortran. So no road blocker here.

1 Like

@ShrirajHegde , please never accept at face value what anyone informs you about what Fortran was not “meant to be”. Literally, no one really knows that and no one has or should have the authority on that. Rather, focus on what Fortran can be, and that’ll be what you and each of the practitioners can make it out to be. It shall ever remain an open canvas.

For the specific matter that has piqued your curiosity, you will recall starting with Fortran 2003 standard revision, the language has recognized the near-ubiquitous existence of the C companion processor and has included facilities toward the same. The end result is the perennial potential for Fortran to be a systems programming language also, barring any of the “mundane” notions of purity, of course!

Thus for a situation like the one you present here, when the going gets tough in Fortran, the tough can turn to C!! You can try the same:

   use, intrinsic :: iso_c_binding, only : c_char, c_int
   use stdio_m, only : putchar, puts
   integer(c_int) :: i, r
   do
      do i = 49, 90
         r = putchar( i ) 
      end do
      r = puts(c_char_"")
   end do
end 

C:\temp>p.exe
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD
123456789:;<^C

The above snippet being served by the following to interface with C <stdio.h>:

module stdio_m
   use, intrinsic :: iso_c_binding, only : c_char, c_int
   interface
      function putchar( i ) result(r) bind(C, name="putchar")
         import :: c_int
         ! Argument list
         integer(c_int), intent(in), value :: i
         ! Function result
         integer(c_int) :: r
      end function 
      function puts( str ) result(r) bind(C, name="puts")
         import :: c_char, c_int
         ! Argument list
         character(kind=c_char,len=1), intent(in) :: str(*)
         ! Function result
         integer(c_int) :: r
      end function 
   end interface
end module
4 Likes

@FortranFan or anyone else,

Can you provide a documentation for Fortran - C interoperability and any tutorial on calling Fortran routines from C and vice-versa?

It’s really hard finding resources for Fortran online.

Depending on your experience with C, you can go straight to the Fortran standard and review it first: https://j3-fortran.org/doc/year/18/18-007r1.pdf

You can then review webpages such as the following for some additional detail:
https://splichal.eu/scripts/sphinx/gfortran/_build/html/interoperability-with-c.html

You can also consider the following book reference: Modern Fortran Explained (MFE) including Fortran 2018
https://oxford.universitypressscholarship.com/view/10.1093/oso/9780198811893.001.0001/oso-9780198811893

And do a search on this forum for “interoperability” and you will see a few hits (I’ve posted several) with targeted snippets such as the one upthread.

3 Likes

It doesn’t cover everything that’s possible, but should get you started.

2 Likes

Thanks, That’s great.

Printing a lot of stuff very frequently on the screen may be a bad idea. It is can make a very fast code become very slow. If you want to print a lot of stuff, print them to a file, simply do

> xxx.out

the xxx.out will record everything on the screen while does not slow down the code. I think at least, the recent versions of Gfortran, by default indeed automatically do the IO buffer.
I have to use

call flush (unit)

to force it not to buffer.

There is GFORTRAN_UNBUFFERED_ALL stuff in gfortran, I believe by default this option is not set as true in gfortran, so gfortran does buffer IO by default.

The thing you said is not unusual, a 5 second can become 1 min or more if you need to print tons of stuff very frequently on the screen. But I feel this slow down may not the fault of gfortran.

Timing several versions give interesting results:

program test
  implicit none
  integer :: i,k
  logical :: multi
  multi = command_argument_count() > 0
  do k=1,10000000
    if (multi) then
!      WRITE(*,'(*(A1))') (achar(i),i=49,90)
!      WRITE(*,'(42A1)') (achar(i),i=49,90)
      WRITE(*,*) (achar(i),i=49,90)
    else
      do i=49,90
        WRITE(*,"(A)",advance="no")achar(i)
      enddo
      print*,""
    endif
  enddo
end program test
>time ./a.out > /dev/null
68.902u 25.599s 1:34.50 99.9%
using @kargl's hint:
>time ./a.out 1 > /dev/null
 7.908u 0.584s 0:08.49  99.8%   using @kargl's hint, list-directed (*) format
12.923u 0.547s 0:13.47  99.9%  as above, (42A1) format
14.673u 0.543s 0:15.21 100.0% as above, (*(A1)) format

@FortranFan’s version, with 10,000,000 executions of the inner loop, completes in

time ./stdio_m > /dev/null
2.236u 0.016s 0:02.25 99.5%

So, it seems, there is a huge overhead added by executing WRITE statement (43 times more in OP version vs. @kargl’s), less dependent on the actual number of characters output. NB., the Fortran-C version is much faster even with 430 million calls to putchar/puts

NOTE: there is a strange problem with Fortran-C version. Compiled with gfortran v. 10 outputs lines ending with extra ‘D’ character:

123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZD

ifort gives expected output ending each line on ‘Z’.
This can be fixed by modifying the @FortranFan’s program unit to

program stdio
  use, intrinsic :: iso_c_binding, only : c_char, c_int
  use stdio_m, only : putchar, puts
  integer(c_int) :: i,k, r,nl
  nl = iachar(new_line('a'))
  do k=1,10000000
    do i = 49, 90
      r = putchar( i )
    end do
    r = putchar(nl)
  end do
end program stdio

Is puts(char_c_"") OK?