Fortran 2023 standard

Consider one possible model for a new intrinsic string type as shown below:

Click to see some "library" code
module string_m

   private

   type :: string_t
      private
      character(len=:), allocatable :: m_s
   contains
      private
      procedure :: write_s
      procedure :: assign_s
      generic, public :: assignment(=) => assign_s
      generic, public :: write(formatted) => write_s
   end type

   generic :: string_t => construct_s

   public :: string_t

contains

   function construct_s( s ) result(new_string)
      character(len=*), intent(in) :: s
      type(string_t) :: new_string
      new_string%m_s = s
   end function

   subroutine assign_s( this, s )
      class(string_t), intent(inout) :: this
      character(len=*), intent(in)   :: s
      this%m_s = s
   end subroutine

   subroutine write_s(this, lun, iotype, vlist, istat, imsg)

      ! argument definitions
      class(string_t), intent(in)     :: this
      integer, intent(in)             :: lun
      character(len=*), intent(in)    :: iotype
      integer, intent(in)             :: vlist(:)
      integer, intent(out)            :: istat
      character(len=*), intent(inout) :: imsg

      ! local variable
      character(len=9) :: sfmt

      sfmt = "(A)"
      if ( (iotype == "DT").and.(size(vlist) >= 1) ) then

         ! vlist(1) to be used as the field width of the character component.
         write(sfmt,"(A,I2,A)", iostat=istat, iomsg=imsg ) "(A", vlist(1), ")"
         if (istat /= 0) return

      end if

      write(lun, fmt=sfmt, iostat=istat, iomsg=imsg) this%m_s

      return

   end subroutine write_s

end module
   use string_m, only : string_t 
   type(string_t), allocatable :: parts(:)
   parts = [ string_t("valve"), string_t("compressor"), string_t("transducer") ]
   call show_second(parts)
   parts(2) = "thermocouple"
   call show_second(parts)
contains
   subroutine show_second(strings)
     type(string_t), intent(in) :: strings(*)
     ! "where does the second element start, and how big is it?"
     ! the answer: what the coder expects, this is not rocket science
     print *, strings(2)
   end subroutine
end
C:\temp>ifort /standard-semantics /free p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.9.0 Build 20230302_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 compressor
 thermocouple

But for the array constructor verbosity and unpleasantness with

..
parts = [ string_t("valve"), string_t("compressor"), string_t("transducer") ]
..

and the needlessly verbose need for a type(string_t) the pieces are all nearly there.

What is missing are the aspects I highlighted above, especially with the inability of a library author to implement the use case of practitioners to have substring data reference of the form parts(3)(1:4) which is quite important.

The issue with the array constructor syntax is nowhere as difficult as made it out be in the context of an intrinsic type STRING. Meaning, the standard can easily work out the rules with something new - say assumed-length, so that

parts = [ string_t : "valve", "compressor", "transducer" ]

can be the equivalent of the far more verbose

parts = [ string_t("valve"), string_t("compressor"), string_t("transducer") ]

This is nowhere as difficult as is made it out to be by @everythingfunctional . The key here is likely to be for the standard to be silent about the underlying model and not presume a length-type parameter exists for the type and therefore the implementations can do what is best for them, say possibly with an underlying ALLOCATABLE component. And without the length-type parameter, the compact syntax gets parsed as done for other features that are similarly syntactic sugar.

2 Likes

This is precisely what the practitioners need to take a note of: this is exactly the indolent argument that places the practitoners last.

So here’s the thing: there are the supposedly international bodies of ISO and IEC who have contracted out the technical work toward the Fortran standard to the US forum of INCITS, otherwise known as J3.

Effectively, ISO has a sole contractor arrangement with J3 (aka INCITS).

In essence, this is the crux of the problem.

Perhaps J3 needs to be fired outright, or maybe ISO / IEC need to find other contractors also. The practitioners of Fortran really need to start thinking outside the box.

Again and again, the argument is the contractor (J3) wants to do too little and too slowly. Always the argument is it is too much work and we do not have enough resources. This is way too stale now.

Imagine your housing association in your living community relying on some public utility (say, internet service) and where the association has contracted it out to a body, even if full of volunteers, who consistently provides you with 10, 15, 20 year old technology in half-baked fashion. There is a limit to how long the residents can put up with the nonsense. The association will have to be forced to look out for other better contractors and for the existing contractor to be read out the riot act.

It is the same exact situation with the Fortran standard.

“700 pages” - my foot. It does not even matter if it is 70,000 pages. The key is to find the right “contractors”. Give others the proper chance and much better outcome can be obtained. As I noted elsewhere, with an open standard, someone like @jacobwilliams can automate so much of the process to make things so much more reliable and faster.

It is beyond time that the poor, persevering practitioners of Fortran question everything.

Someone who codes in Fortran to develop scientific and engineering solutions: please tell me: who is any of the names on list any more of an authority than you or your colleague to decide what is useful or can prioritize for you what is important. When was the last time any of them communicated with you with passion and earnestness to get you to write better and more expressive Fortran code? There is no humility on that list, believe me - few of them can author modern Fortran code or write compilers or have passion for Fortran - they simply do not have any basis to decide for the Global Community of Fortranners, none.

2 Likes

So, the iso_varying_string module (which I have an implementation of by the way), is very nearly there. What is missing is:

  • A way for a derived type to overload array index/substring operations
  • A way to define named constants of derived types with private and/or allocatable components
  • Have overloaded assignment be used in array constructors (probably the syntax shown will be workable)

IMHO it would be better for the committee to get those things working so practitioners can solve their own problems, than solve every problem with new intrinsics.

I agree that the situation is not working well, but this is a backwards analogy. ISO does not pay J3 to do the work, but rather the members of J3 must pay ISO. This is (IMO) where the problem lies.

We really do have resource constraints. If we could get more volunteers (and if they didn’t have to pay to join maybe we would) perhaps we could accomplish more. But simply asserting “this should be doable” and expecting others to “make it so” is not fair to those of us actually doing the work.

As one of the names on that list, I take exception and offence. I am one week from tomorrow teaching a course on modern Fortran basics to >100 people, not to mention the 3 online courses I’ve produced, the couple of GSoC students I’ve mentored, the monthly user group meeting I host, and the dozen or so open source Fortran libraries I’ve written. To suggest that I don’t care about helping users of Fortran is an outright lie. What exactly have you done to help?

8 Likes

Please stop speaking for all “practionners” as if they were all sharing your points of view.

This is a fair complaint, but I think @FortranFan 's passion should not be brushed away. We have a very excellent language in Fortran: compiled, with first class support for arrays, and offering a variety of programming styles with good support (mostly imperative and procedural, but also with functional and object-oriented elements available in more recent versions).

It is important for a programming language to have outspoken users that are loud about what they like, what they don’t like, and what they want for the language going forward. If you feel very strongly, and differently, from the views often expressed, then feel free to voice those opinions. A diverse set of experiences and inputs is also valuable to successful development for all users of the language.

Personally, I find myself often agreeing with the points set forward by @FortranFan, but cannot quote the standard as readily as many users on this DIscourse. I simply use the language, pretty much every day, and know from user experience what I like, don’t like, and wish was different.

3 Likes

There are facts in the above discussions that no one can deny. For example, Fortran programmers had wanted generics and metaprogramming, for years, long before half a dozen new languages with generics were born. The strongest argument I remember I heard from a committee member was that no one on the committee “knew the topic well enough” or “was interested in taking the lead on the subject” (please correct me if I misremembered the quotes). So this critical community need was “apparently” neglected for years practically until now.
This is not the right way for a representative committee to address the community’s needs.
If the mayor of my town ignores my needs and requests, just because he does not know how to handle them, their name will not appear on my ballot in the next election. I have never heard of an open election for the Fortran standard committee. I don’t know if other programming languages have it, either. But that is how democratic societies ensure efficiency and productivity in their governing body.
On a side note, I have deep respect and high regard for many of the committee members I have had a chance to know and interact with for some time, either directly or indirectly. I know of their deep knowledge of compilers, languages, and vision, making them unique worldwide and a true asset for the Fortran language and community.

2 Likes

@FortranFan I agree with almost all the points you are making. When you are making the points, please try not to attack people. For example, it’s not @everythingfunctional fault that Fortran has the issues that it has. He is trying his best (thank you Brad!). I know most people at the committee in person, they are all great people. I think it’s the process itself that needs to be improved, I think all these features should be implemented in compilers first, users should use it, and only then the committee should standardize it. Right now the compilers are a little bit behind, but I think we’ll get there that compilers will start leading the effort.

8 Likes

(stdlib_string)[string_type – Fortran-lang/stdlib] could be used as a starting point as it proposes a string_type and most of (all?) the intrinsics are overloaded for this string_type, as well as IO operations.
A stringlist_type is also provided in stdlib
Some of the questions in this thread were already discussed and implemented in stdlib. I don’t say it is the way to go, but at least it could be a good start to reflect on (and maybe to implement in @certik LFortran easily for testing)?

stdlib example:

program example_concatenate_operator
  use stdlib_stringlist_type, only: stringlist_type, operator(//)
  use stdlib_string_type, only: string_type
  implicit none

  type(stringlist_type)          :: first_stringlist, second_stringlist
  type(string_type), allocatable :: stringarray(:)

  first_stringlist = first_stringlist//"Element No. one"
! first_stringlist <-- {"Element No. one"}

  second_stringlist = string_type("Element No. two")//first_stringlist
! second_stringlist <-- {Element No. two, "Element No. one"}

!> Creating an array of 2 string_type elements
  stringarray = [string_type("Element No. three"), string_type("Element No. four")]

  second_stringlist = first_stringlist//stringarray
! second_stringlist <-- {"Element No. one", "Element No. three", "Element No. four"}

  second_stringlist = ["#1", "#2"]//second_stringlist
! second_stringlist <-- {"#1", "#2", "Element No. one", "Element No. three", "Element No. four"}

  first_stringlist = first_stringlist//second_stringlist
! first_stringlist <-- {"Element No. one", "#1", "#2", "Element No. one", "Element No. three", "Element No. four"}

end program example_concatenate_operator
7 Likes

My main point is that I do not support this recurrent bashing of the commitee, and particularly when it comes about the commitee members.

10 Likes

I very much like @everythingfunctional’s take: focusing on these underlying specs would have far wider reach alone rather than only focusing on improving strings.

At least, this is my experience: I stumble upon those limitations fare more often as I deal with derived/polymorphic types. Instead, typing a couple more characters to enable variable-length string initialisers is not a big deal to me. Most of the friction is already removed by using derived string types like @jeremie.vandenplas pointed out.

3 Likes

Yes, we can implement to natively understand the stringlist_type and map it to the internal list[str] implementation, so you get high performance.

However I suspect performance is not the main issue here, but rather easiness of use.

Good point — it seems the proposed “string” type is almost equivalent to the current type(string_type) from stdlib, which is allowed to be used as an array element. However notice that even stdlib introduces stringlist_type, so it’s not enough to use it inside arrays, you still want to have a list of strings.

So I think lists are still useful for Fortran, even if it already has arrays, just like they are useful for Python (even though it has NumPy arrays). The main difference is that you can quickly append to a list, while you can’t quickly do that to an array.

3 Likes

I tend to agree also. I proposed these two a while back:

If we had those then we could do a lot.

A “standard” string class is crucial. We can’t have every library just keep implementing their own:

type string
  character(len=:),allocatable :: s
end type string

That is just chaos for a library ecosystem. So, either it needs to go into the language or the language needs to give us the tools to make the class we want and standardize that in the community (e.g. in stdlib).

12 Likes

Please stop pandering to the WG5 and J3 committees who want to do little and too late as if that helps Fortran generally and that all other practitioners share your point of view.

So J3 and thus effectively WG5 are vehemently informing the practitioners they will not do either of the above, it will not go into the language nor will the language give the “tools” toward the string subsection reference, what is indicated here as overloading ( .. ).

Note @ClivePage back in 2015 too had expressed the need for improved string handling in Fortran - J3 and WG5 have not offered anything meaningful since.

The practitioners can go pound sand is that what J3 is telling you. J3 is not going to change its mind in the current scheme of things, they want to do too little, too late - just look at “enumeration type”, it started in the work toward Fortran 2000 and it is not clear if even Fortran 202Y will offer something usable. Fortran 2023 messed it up. It is always excuses, excuses, excuses.

So now what?

This is why I suggest the practitioners start thinking differently.

@jeremie.vandenplas , @certik, et al.,

First, note this with string_type in Fortran stdlib. The use of SEQUENCE is really a kluge and generally not advisable.

But the notion behind the kluge is correct: a basic type such as string_type should not be extensible.

It is also with such a need in mind that I had proposed back in 2019 for the Fortran 2023 revision to introduce the ability to author inextensible types.

Regrettably, J3 refuses to work on this for 2023 and has yet again decided to so for 202Y. It is such a simple thing to add to the language, such a low-hanging fruit with hardly much of any work in needed toward the standard and compiler implementations. And yet this won’t make it in. It is entirely the no soup for you line of thinking, it has no technical merit, only dissing.

You can research C++ standard library history to know there are classes which are best marked “final” i.e., inextensible in Fortran parlance.

STRING is one such as noticed with Fortran stdlib attempt. This is yet another reason to make STRING an intrinsic type.

Fortran 202X Feature Survey Results - Final (wg5-fortran.org) is the result of a six-month user survey run 2017-2018 for what should go into what became Fortran 2023. Many of the most popular suggestions did make it in, but not all. Generics took a while to decide on an approach and was deferred to 202Y, but the Generics subgroup has made significant progress on a specification that seems workable.

READ into allocatables, though popular (and a favorite of mine), turned out unworkable except in limited cases - that did make it into 2023. UNSIGNED did not. Only a single comment suggesting what could be a “string” type was received. We struggled with exceptions, as have other languages - I’d still like to see something done there, but don’t know what would meet the needs and not slow down code that doesn’t use them.

As I’ve written before, a major obstacle for getting things done in the standard is that most of the actual work is done by a handful of members. Just writing a specifications paper would be helpful. I do applaud the Generics subgroup for focusing on delivering a solution that may not meet everyone’s needs, but significantly advances capabilities of the language.

3 Likes

Could you please point to where this is in the standard?

See section 2.2 of https://wg5-fortran.org/N2201-N2250/N2212.pdf

If there were a string type we would use it.

To return to the original thread topic, a BIT type was implemented in the Gould-SEL extended Fortran 77 compiler for the Concept series machines. Variables of this type could be used in any context that logical variables could be used. BIT arrays could be equivalenced to objects of other data types. We have seen 3 use cases:

i. Constructing numbers to send to external hardware. In migrating code to standard Fortran we have found nothing which couldn’t be done better with bit intrinsics.

ii. Constructing assembler commands which the SEL could execute in its own registers. PLEASE DON’T DO THIS AT HOME!

iii. Creating very large logical arrays which otherwise would not fit in memory. This is actually useful.

For the 3rd reason I would support inclusion in the standard. It would also save us some work in migrating code.

Was the BIT type implemented in other compilers?

3 Likes

This is primarily the main reason why I used to think that a BIT type would be useful. On the other hand, in contrast to F77, compilers have now the ability to provide 1 byte logicals and most of them do, which probably makes the problem less critical than it used to be (which doesn’t mean that a BIT type would not be useful).