Writing to a file or a string with the same function

I have various functions that carefully log values in a file, along the line of :

subroutine log_conditions(unit, temperature, pressure)

  integer, intent(in) :: unit
  real, intent(in) :: temperature, pressure
  
  character(len=10) :: date, time
  
  call date_and_time(date, time)
  
  write(unit, "(a, a, a, a, f0.3, a, f6.0, a)") "[", date, time, "] The temperature is ", &
  temperature, "°C, the pressure is", pressure, " Pa."

end subroutine

I can pass a unit number associated with a file, or with the standard output/error.

But can I make this function work on a string ? The write statement in itself can take an integer or a string :

  character(len=40) :: string
  integer :: unit
  
  unit = 6
  write(unit, "(a)") "Logging to a unit"
  write(string, "(a)") "Logging to a string"
  
  print *, "string = '", trim(string), "'"

But this does not work on my log_conditions function, because it accepts only an integer as first argument. Somehow I would have to bind a unit to string, just like open binds a unit to a file.

Is this possible?

I could, of course, make two versions of my function, one taking an integer, the other a string, but it would be a shame.

Why don’t you write two subroutines (one taking an integer as first argument and one taking a string) and simply create an interface redirecting to these two procedures?

I would make unit and str (the string to be written to) optional arguments and do this:

subroutine log_conditions(temperature, pressure, unit, str)

  real, intent(in) :: temperature, pressure
  integer, intent(in), optional :: unit
  character (len=*), intent(out), optional :: str
 
  
  character(len=10) :: date, time
  
  call date_and_time(date, time)
  
  if (present(unit)) write(unit, "(a, a, a, a, f0.3, a, f6.0, a)") "[", date, time, "] The temperature is ", &
  temperature, "°C, the pressure is", pressure, " Pa."
  if (present(str)) write(str, "(a, a, a, a, f0.3, a, f6.0, a)") "[", date, time, "] The temperature is ", &
  temperature, "°C, the pressure is", pressure, " Pa."
end subroutine

If you want to write the output list only once (and therefore have only place to make changes) you could store the output in a local character variable and then write it to a unit and/or a string argument:

subroutine log_conditions(temperature, pressure, unit, str)

  real, intent(in) :: temperature, pressure
  integer, intent(in), optional :: unit
  character (len=*), intent(out), optional :: str
  character (len=1000) :: str_ ! choose a len that is large enough
 
  
  character(len=10) :: date, time
  
  call date_and_time(date, time)
  write(str_, "(a, a, a, a, f0.3, a, f6.0, a)") "[", date, time, "] The temperature is ", &
  temperature, "°C, the pressure is", pressure, " Pa."
   
  if (present(unit)) write(unit, "(a)") trim(str_)
  if (present(str)) write(str, "(a)") trim(str_)
end subroutine
2 Likes

I generally try to adhere to the single responsibility principle. The procedure you show violates that principle by doing formatting and output. Thus, in my projects I have procedures that do formatting and only produce strings. Where those strings go is a decision made elsewhere.

You can define a derived type , and overload the write

module log_mod
    implicit none
    type log_t
        real :: temperature, pressure
    contains
        generic::write(formatted)=>log_conditions
        procedure,pass::log_conditions
    end type log_t
contains
    subroutine log_conditions(this,unit, iotype, v_list, iostat, iomsg)
        class(log_t), intent(in) :: this
        integer, intent(in) :: unit
        character(*), intent(in) :: iotype
        integer, intent(in) :: v_list(:)
        integer, intent(out) :: iostat
        character(*), intent(inout) :: iomsg
          
        character(len=10) :: date, time
  
        call date_and_time(date, time)
        write(unit, "(a, a, a, a, f0.3, a, f6.0, a)") "[", date, time, "] The temperature is ", &
        this%temperature, "°C, the pressure is", this%pressure, " Pa."
    end subroutine log_conditions
end module log_mod

program main
    use log_mod
    implicit none
    real::t,p
    type(log_t)::my_log
    character(len=512)::str
    !
    t=1.00
    p=12.3
    write(*,*)log_t(t,p)
    !
    my_log=log_t(30.3,23.4)
    write(str,*)my_log
    write(*,"(A)")str
end program main
1 Like

Very interesting, but it’s turning a “simple” procedure into an object, and this may not a small refactoring. The unit number was used to alternate between console and file output, by associating stdout to the unit or not.

This code is a porting of legacy OpenVMS code, where it was possible to redirect a unit number to a mailbox, to pass the logs to another process for example.

1 Like

I use a function STR that returns a string and can take up to twenty intrinsic scalars. Then the string can be written to a file(s) or passed to another procedure in some way or another. If a float needs refined I can pass it as a call to FMT to specify a specific format. I can then pass the string to a number of other procedures to record it in a log, write it to multiple files, stick it in an SQLite3 file, pass it over the network, …

The M_framework module is more recent and includes a logging utility but the simple components are in M_msg. If you use fpm(1) they are trivial to try. If all your messages use just a single format a print procedure is not bad; but if writing a lot of unique messages using something like string allows you to see the full message where it is being called which can make the code clearer in my experience.

https://urbanjost.github.io/M_msg/man3.html

1 Like

Neat. I have sometimes wished to write a Fortran procedure that can take any number of arguments of any type. The built-in print statement has this feature. How @urbanjost does it is to declare many class(*),intent(in),optional arguments, as shown in his code

pure function msg_scalar(generic0, generic1, generic2, generic3, generic4, generic5, generic6, generic7, generic8, generic9, &
                       & generica, genericb, genericc, genericd, generice, genericf, genericg, generich, generici, genericj, &
                       & sep)
implicit none
class(*),intent(in),optional  :: generic0, generic1, generic2, generic3, generic4
class(*),intent(in),optional  :: generic5, generic6, generic7, generic8, generic9
...

His function takes up to 20 arguments, which is more than needed in almost all cases, but a code could be written to generate source code for a function that takes N > 20 arguments. So with automatic code generation you can get in Fortran some of the flexibility you have in Python.

There are many ways to have your program decide where to write its output, but as far as I know, they all require two separate write statements, one for the integer file unit and the other for the output character string. It could be two separate subroutines, or one subroutine with some kind of internal logic to decide which of the write statements are executed, but I think all of the solutions will eventually require two write statements.

A similar issue arises when you want to write the same output to more than one unit. However, in this case the programmer can put the unit numbers in an array and loop over the elements of the array as the output unit while using only a single write statement.

Finally I would caution against using a function to do i/o, use a subroutine instead. The reason is that it is easy to inadvertently nest i/o statements within such functions, which is not allowed in fortran (with a few exceptions). Debugging such code can be difficult.

1 Like