Why are parens required around format strings?

Here is a counter example.

program xxx
   write(*,'(g0.4)') .01234, ".01234"
end program xxx

$ gfortran xxx.f90 && a.out
0.1234E-1
.01234

As you can see, that format results in a field that is three characters longer than necessary.

OK, but maybe you can use this?

D:\Projects>type t.f90
program xxx
   write(*,'(f0.7)') .01234567
end program xxx
D:\Projects>ifx -nologo t.f90

D:\Projects>t.exe
.0123457

Admittedly, F format won’t handle the string, but I think Fortran is expressive enough as it is.

Yes, of course you can almost always find an existing format that will print a particular value correctly, but it is nontrivial. Because it is nontrivial, it should be built in to the language, and programmers should not be required to reinvent the wheel for each floating point value. In the example I give above, the decision is whether to use an exponent field or to eliminate the exponent field and switch to an f format. In other cases, there might be optional signs that can be removed, or leading zeros that can be removed. Sometimes there are multiple formats that all result in the same output width, in which case the fortran standard should select one of them so that the output is well defined. The whole issue is nontrivial.

And then there is the other problem of finding the right format to print the maximum number of significant digits in a given field width. That is also a nontrivial problem.

1 Like

I wrote a module called es0f0i0mod.f90 to simulate I0, F0, or ES0E0 format writing default integer, or single or double precision real minimum-length character strings
with a given number of digits after the decimal point as type character functions. A benefit was that many of my programs can just use A format instead of mixtures of A, F, ES and I. It works with gfortran, ifx and ifort in a Linux system.Here it is: 176 lines of which the first 54 are comments describing it.

! File es0f0i0mod.f90 is a Fortran 2018 module with public functions i0,f0,es0
! to simulate I0,F0,ES0E0 formats writing default integer, or default real
! (kind(1e0), or double precision (kind(1d0)) minimum-length character strings.
! A Fortran 95-compliant version is number0mod95.f90, much longer than this.
! By J F Harper, Mathematics, Victoria University of Wellington, NZ
!
! Public entities defined in this module are
! two integer constants: sp = kind(1.0), dp = kind(1d0);
! two pure non-generic scalar character functions i0, up;
! two pure generic scalar character functions: f0, es0, each with private
!     specific forms for real kinds sp and dp.
!
! Compilers vary in their own treatments of leading zero and optional + sign
! because past Fortran standards differed, and f95 was ambiguous. This module
! lets users choose their own treatment with SP (writing + on nonnegative
! output) and LZ (which is treated like the Fortran 2023 LZP; the Fortran 2023
! LZ is processor-dependent).
!
! Options may be in UPPER or lower case. All arguments are scalar intent(in).
!
! Function up(string) returns string, of type character, with its lower case
! characters a-z converted to upper case A-Z, but no other changes, e.g.
! up('a+B') = 'A+B'
!
! Function i0(n,opt) returns a character string giving the value of  n.
!   Arguments:
!   n: default integer;  
!   opt: optional character string. If up(opt) contains SP, + is the first
!        character of the output if n >= 0.
!
! Function f0(x,d,opt) returns a character string giving the value of x
! in F0.d format, with leading zero if requested or if without it there 
! would be no digits at all. If separate positive and negative zeros are
! supported then f0(-0.0,n) begins with a - sign. Arguments:
!   x: value to be written by f0 [double precision or default real]
!   d: number of digits to be written after the decimal point [integer]
!   opt: optional character string. If up(opt) contains LZ, 0 is inserted
!        before the decimal point if there would otherwise be no digits there
!        (like Fortran 2023 LZP editing);
!        if up(opt) contains SP, + is the first character of the output if it
!        would not have been -
!
! Function es0(x,d,opt) returns a character string giving the value of x
! in ES0.dE0 format; Arguments:
!   x: value to be written by es0 (double or single precision).
!   d: number of digits after the decimal point.
!   opt: optioinal character string.
!   If up(opt) contains SP, the output begins with - or + but if not, it 
!   begins with either - or the first digit e.g. es0(314.,1) is '3.1E+2'
!   If up(opt) contains LE (meaning Lower case E) then the E is replaced by e.
!
! 17/08/23 ES0.0E0 replaced by loop over w increasing in ESw.0E0 until output
!          contains no * because not all compilers have yet implemented ES0.0E0
! 21/08/23 Options implemented: LZ for f0, LE for es0, SP for i0,f0,es0.
module es0f0i0mod
  implicit none
  private 
  public sp,dp,i0,f0,es0,up 
  integer,parameter :: dp = kind(1d0) ! double precision kind
  integer,parameter :: sp = kind(1.0) ! default real = "single precision" kind
  interface f0 
     module procedure dpf0,spf0 
  end interface f0
  interface es0
     module procedure dpes0,spes0
  end interface es0

contains

  pure function                i0(n,  opt)
    character(:),allocatable:: i0
    integer,intent(in)      ::    n
    character(*),intent(in),optional::opt
    character:: out*(range(1)+2), msg*200 ! f2023 will remove need for out
    character(:),allocatable:: upopt,fmt
    integer  :: ios
    upopt = ' '
    if(present(opt)) upopt = up(opt)
    fmt = merge("(SP,I0)","(SS,I0)",index(upopt,'SP')>0)
    write(out,fmt,iostat=ios,iomsg=msg) n  
    if(ios==0)then
       i0 = trim(adjustl(out))
    else
       i0 = '*** i0 error: '//trim(msg)
    end if
  end function i0
 
  pure function                spf0(x,n,opt)
    character(:),allocatable:: spf0
    real(sp),intent(in)::           x   
    integer,intent(in) ::             n     ! using f0.n format
    character(*),intent(in),optional::  opt ! for options
    spf0 = trim(dpf0(real(x,dp),n,opt))
  end function spf0

  pure function               dpf0(x,n,opt) 
    character(:),allocatable::dpf0
    real(dp),intent(in)::          x   
    integer,intent(in) ::            n     ! using f0.n format
    character(*),intent(in),optional:: opt ! for options
    character(:),allocatable:: upopt,fmt !!,         res
    character:: out*(range(1d0)+4+abs(n)), msg*200
    ! so len(out) = max possible space for x in f0.n format
    integer  :: ios
    if (x/=x) then
       dpf0 = 'NaN'
    else if (n<0) then
       dpf0 = '*** F0.n error: n = '//i0(n)//' < 0'
    else ! n >= 0 and x is finite or Inf or -Inf 
       upopt = ' '
       if(present(opt)) upopt = up(opt)
       fmt = '(SP,F0.'//i0(n)//')' ! SP simplifies LZ code; see non-SP below 
       write(out,fmt,iostat=ios,iomsg=msg) x
       if(ios/=0) then
          dpf0 = '*** f0 error: '//msg
       else
          dpf0 = trim(adjustl(out))
          if(index(upopt,'LZ')>0) then ! insert leading zero if needed
             if (dpf0(1:2)=='-.' ) dpf0 = '-0'//dpf0(2:)
             if (dpf0(1:2)=='+.' ) dpf0 = '+0'//dpf0(2:)
          end if
       end if
       if(dpf0(1:1)=='+'.and.index(upopt,'SP')==0) dpf0 = dpf0(2:) 
    end if
  end function dpf0

  pure function               spes0(x,d,opt)
    character(:),allocatable::spes0
    real(sp),intent(in)     ::      x   
    integer,intent(in)      ::        d
    character(*),intent(in),optional::  opt
    spes0 = trim(dpes0(real(x,dp),d,opt))
  end function spes0

  pure function               dpes0(x,d,opt) ! simulate ES0.dE0 writing
    character(:),allocatable::dpes0
    real(dp),intent(in)     ::      x   
    integer,intent(in)      ::        d          
    character(*),intent(in),optional :: opt
    character(:),allocatable:: fmt, upopt
    character:: out*(d+12), msg*200
    integer eplace,w,ios
    if(x/=x) then
       dpes0 = 'NaN'
    else if(d<0) then
       dpes0 = '*** ESw.dE0 error: d = '//i0(d)//' < 0'
    else
       upopt = ' '
       if(present(opt)) upopt = up(opt)
       do w = 3,len(out)! to avoid ES0, not yet available in some compilers
          fmt = "(SS,ES"//i0(w)//"."//i0(d)//"E0)"
          write(out,fmt,iostat=ios,iomsg=msg) x
          if(ios/=0) dpes0 = 'es0 error: '//msg
          if(index(out,'*')==0.or.scan(out,'nNiI')/=0) exit
       end do
       dpes0 = trim(adjustl(out))
       eplace = index(dpes0,'E')
       if(index(upopt,'LE')>0 .and. eplace/=0) dpes0(eplace:eplace) = 'e'
       if(index(upopt,'SP')>0 .and. dpes0(1:1)/='-') dpes0 = '+'//dpes0
    end if 
  end function dpes0
  
  pure function               up(string) 
    character(*),intent(in)::    string
    character(len(string)) :: up
    character(*),parameter :: upper = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ', &
         lower = 'abcdefghijklmnopqrstuvwxyz'
    integer i,ilower
    up = string
    do i = 1,len(string)
       ilower = index(lower,string(i:i))
       if(ilower>0) up(i:i) = upper(ilower:ilower)
    end do
  end function up
    
end module es0f0i0mod
4 Likes

@Harper do you want to submit your code to stdlib? It might be a good fit there.

Thank you @certik. My module isn’t ready for stdlib yet. In one test case gfortran, ifx and ifort all agreed but AMD flang gave a different result. Lfortran gave a compile-time seg.fault.

1 Like

My favourite string manipulation mechanism in Python, by far, is the f-string. I think it solves nicely the printing formatting (non structured, I agree that Fortran structured formats are powerful):

i=1
a=1.123456789
text="this"

print(f"{i} is an integer, {a:1.2f} is a rounded real and '{text}' is text")

Would something like that be possible to have in Fortran?

What is the most elegant way to do that with the current Fortran standard?

I guess something like this works:

print "(i0,' is an integer, ', f1.2, ' is a rounded real and ''',a,''' is text')", i, a, text

Which is OK, but not as nice as the f-string

1 Like

@eelis, yes, f-strings are my favorite as well in Python for string formatting. To do this in Fortran, why not exactly the same syntax:

character(:), allocatable :: s, text
integer :: i
real :: a
i=1
a=1.123456789
text="this"
s = f"{i} is an integer, {a:1.2f} is a rounded real and '{text}' is text"
print *, s ! or rather print(s) !!
1 Like

If it is that you can place the format write with the value, creating a little function like the following FMT procedure . can let you do that, and is also handy for converting any numeric value to a string. I have related functions and overloads of the plus and concatenation operators that perhaps get closer but the fmt function is pretty handy. For someone not familiar with the Fortran formatting descriptor “language” like repeat counts and : and so on (which make it particularly nice for printing arrays) something like FMT() is easier to understand as well. It is something handy to use now with Fortran as-is but it would be nice for Fortran to have something like that built-in. Note the format string does not need surrounding parens, which gets back to the more specific OP (Original Post)

program main
implicit none

integer                      :: i
real                         :: a
character(len=:),allocatable :: text

character(len=4096) :: line
character(len=*),parameter   :: asis='(*(g0))'

   i=1
   a=1.123456789
   text="this"

  !py!print(f"{i} is an integer, {a:1.2f} is a rounded real and '{text}' is text")

   print asis,i," is an integer, ",fmt(a,'f0.2')," is a rounded real and '",text,"' is text"

  ! put it into a string with internal write
   write(line,asis)i," is an integer, ",fmt(a,'f0.2')," is a rounded real and '",text,"' is text"
   call doop(trim(line)) ! do something with line

  ! concatenation works too and can be passed as an argument, so more compact in some cases
   line=fmt(i)//" is an integer, "//fmt(a,'f0.2')//" is a rounded real and '"//text//"' is text"
   print asis,trim(line)

contains

subroutine doop(string) ! do some operation on string
character(len=*),intent(in) :: string
integer :: i
   write(*,asis)(string(i:i),i=len(string),1,-1)
end subroutine doop

recursive function fmt(generic,format) result (line)
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64, real32, real64, real128

! ident_4="@(#) M_framework__msg fmt(3f) convert any intrinsic to a string using specified format"

class(*),intent(in)          :: generic
character(len=*),intent(in),optional  :: format
character(len=:),allocatable :: line
character(len=:),allocatable :: fmt_local
integer                      :: ios
character(len=255)           :: msg
character(len=1),parameter   :: null=char(0)
integer                      :: ilen
   if(present(format))then
      fmt_local=format
   else
      fmt_local=''
   endif
   ! add ",a" and print null and use position of null to find length of output
   ! add cannot use SIZE= or POS= or ADVANCE='NO' on WRITE() on INTERNAL READ,
   ! and do not want to trim as trailing spaces can be significant
   if(fmt_local == '')then
      select type(generic)
         type is (integer(kind=int8));     fmt_local='(i0,a)'
         type is (integer(kind=int16));    fmt_local='(i0,a)'
         type is (integer(kind=int32));    fmt_local='(i0,a)'
         type is (integer(kind=int64));    fmt_local='(i0,a)'
         type is (real(kind=real32));      fmt_local='(1pg0,a)'
         type is (real(kind=real64));      fmt_local='(1pg0,a)'
         type is (real(kind=real128));     fmt_local='(1pg0,a)'
         type is (logical);                fmt_local='(l1,a)'
         type is (character(len=*));       fmt_local='(a,a)'
         type is (complex);                fmt_local='("(",1pg0,",",1pg0,")",a)'
      end select
   else
      if(format(1:1) == '(')then
         fmt_local=format(:len_trim(format)-1)//',a)'
      else
         fmt_local='('//fmt_local//',a)'
      endif
   endif
   allocate(character(len=256) :: line) ! cannot currently write into allocatable variable
   ios=0
   select type(generic)
      type is (integer(kind=int8));     write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (integer(kind=int16));    write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (integer(kind=int32));    write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (integer(kind=int64));    write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (real(kind=real32));      write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (real(kind=real64));      write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (real(kind=real128));     write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (logical);                write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (character(len=*));       write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
      type is (complex);                write(line,fmt_local,iostat=ios,iomsg=msg) generic,null
   end select
   if(ios /= 0)then
      line='<ERROR>'//trim(msg)
   else
      ilen=index(line,null,back=.true.)
      if(ilen == 0)ilen=len(line)
      line=line(:ilen-1)
   endif
end function fmt

end program main
$ fpm run std

fpm: Entering directory '/cygdrive/c/users/jost/github/fun/prints'
Project is up to date

1 is an integer, 1.12 is a rounded real and 'this' is text
txet si 'siht' dna laer dednuor a si 21.1 ,regetni na si 1
1 is an integer, 1.12 is a rounded real and 'this' is text

fpm: Leaving directory '/cygdrive/c/users/jost/github/fun/prints'
2 Likes

That’s amazing! Very imaginative and resourceful. Thanks a lot!

Have you got that construction in some fpm package? I’d be so happy to use that.

2 Likes

https:GitHub.com/urbanjost/M_overload

has it as got and // and .fmt. But the overloads broke several compilers last I tried. Also in m_framework and at least two others to avoid circular dependencies in the registry. I was actually working on simplifying that as m_strings has duplicate functionality in converting between numbers and strings and there are several discussed in discourse that are faster or trim and round nicer than some I have. So funny you should ask. So the stabile one is in the overload module. The nicest one that trims trailing zeros and such I need to upload but my internet has been off for nearly a day.

That module was started just to demonstrate simple overloading for people not ready to read how to do arbitrary precision math with overloads ( which is cool but a bit long) but can grow on you.

It was originally in m_msg which was simple with no dependencies but got duplicated when I started breaking GPF into smaller fpm packages but I expect that to pay off when we have a production registry.

So yes, it is in too many!

2 Likes

Nice work! There are many faculties that fixes small, yet annoying issues that I discovered when doing AOC last year. I have known them before, but when I went pure Fortran to solve those general problems (where one typically would like to use a prototyping language), it became evident that something should be done about it. I guess sthe stdlib is a great effort to that direction. I would love to see your overload module there.

Needless to say, I starred your repo.

These f-strings look neat but are less flexible than the existing internal WRITE feature that can use the full power of formats and I/O control lists. I don’t disagree that they look nicer for simpler cases, but again they feel like syntactic sugar to me as they just represent a different way of expressing a small subset of what existing syntax can do.

Fortran I/O feels like a language in itself, and that is why I will support the f-string to have something that is workable on a small subset of it (as we all know in python it’s pretty powerful). :grinning:

I also think if we try to combine the full capabilities of Fortran I/O with f-string in some sane way, something as powerful as the Python f-string can be created.

2 Likes

(Note: The internal write statement saves the result to a string (character type), as opposed to writing to a file.)

Yes, f-strings are a subset of that technically, but I think it’s almost a complete subset. The I/O control list has things like fmt, advance, iostat, unit, etc., I don’t know how many of these are useful for an internal write.

Any statement like:

write (...,...) a, b, c, d

should be possible to express using an f-string. I think even implied do loops could be made to work inside f-strings.

Perhaps there is some complex format string that might not be possible to write as an f-string.

My experience from Python is that f-strings cover almost all use cases that I need in practice, and replaced my previous usage of % and .format formatting.

2 Likes

I agree. There are lots of features, and many ways to do the same, or almost the same thing, with those features. However, there are a few things that are missing. I’ve already mentioned the two minimum field output options for floating point that are nontrivial to replicate. Another set of missing features involve reading an item of unknown field width. For example, on output, the i0 and g0 descriptors write out an integer value in a minimum field width. But these descriptors cannot similarly read in integer values from an arbitrary field width. Instead, the programmer must read the input line into a character string (or a character array), then manually parse to locate the beginning and end of the field, and then read the value from that field (using list-directed input, or with the appropriate fixed field width descriptor). That seems like a lot of work the programmer must do in order to achieve a common, even frequent, task. It would be much simpler for the programmer to use nonadvancing i/o with a field descriptor that just specifies the type and not the width, leaving the record pointer positioned after the field. Some compilers (the VAX f77 compilers, for example) did have an extension to do that, but that option has never been revived in any of the fortran standards. This would be particularly useful when combined with modern nonadvancing i/o.

5 Likes

Former VAX FORTRAN-77 project leader here, and I can’t figure out what you’re referring to. VAX FORTRAN allowed “short field termination” on input, where a comma or the end of a record would reduce the width of the data field to the characters up to that point. It’s not quite what you’re describing. Intel Fortran still supports this extension.

Didn’t the dec/vax compilers support things like

read(n,'(i)') int

where the input field could be of arbitrary width?

No, but I can see how you might think that. If you don’t supply a width, a default is provided based on the type. For a four-byte integer, (i) is equivalent to (i12). See Default Widths for Data Edit Descriptors (intel.com)

Above I mentioned an extension called “short field termination”, and on further reading I find I mischaracterized it. A short record doesn’t trigger this, only a comma following the value. Terminating Short Fields of Input Data (intel.com)

I’m not sure where you figured in non-advancing reads, which VAX FORTRAN certainly didn’t have. In no case would it leave the current position in the middle of a record.

So let’s fast-forward to DEC Fortran 90, which did have non-advancing reads. If the feature you seem to be suggesting was there, then consider the following program:

i = 999
j = 999
read (*,'(i)',advance='no') i
read (*,'(i)') j
print *, i, j
end

and an input of 3 4. You would expect the values 3 and 4 to be printed. What happens instead is that the first read fails because the default width of 12 is greater than the length of the record.

1 Like

It looks like I did misremember the feature. By your description of the (i) format in DEC/VAX fortran, if the input had been 3,4, with the two commas, then a read statement would have resulted in the expected values, right? And if extended to modern fortran with nonadvancing i/o, the two values could also be read with two separate read statements, right?