Why do we need TYPEOF?

When, at last, we have generics I have seen several posts which use the keyword TYPEOF to specify that the type of one argument should be the same as another. Is it necessary to have a new keyword? If x is a variable, argument, function etc. can TYPE(x) mean anything other than the type of x? I raise this because we write KIND(x) to get its kind. Why not TYPE(x) to get its type? One day, when we have access to the internals of arithmetic processors we may define our own kinds (We did something like this in http://simconglobal.com/Testing_the_Numerical_Precisions_Required_to_Execute_Real_World_Programs.pdf). To have KIND(x) but TYPEOF(x) might be another oddity to explain to immigrants from other languages.

3 Likes

I have a similar question about CLASS(*) and TYPE(*). Why do we need both (and yes I know that TYPE(*) is targeted at C-interop). Of course if it was up to me the CLASS keyword would have never entered the language. I would have much preferred making polymorphism an attribute of a derived type something like

type(atype_t), polymorphic :: a_t

I don’t think so. However, when reading a code, it would not be always obvious to quickly determine if TYPE(x) is “the type of x” or “the derived type x”.

Actually KINDOF(x) would have been a better choice :wink:

@PierU
You can’t have a variable called x and a type called x in the same scope. I don’t think that the similar syntax would cause a problem. Note that this is not the case for (non-standard) structures - you can have a structure with the same name as a variable and this caused a lot of hassle in writing fpt. The Fortran standard got this one right.

TYPE would be far from the only keyword/intrinsic with multiple uses. Try REAL:

REAL (KIND=kr8) :: x,y,z

r = REAL(i4)

And two non-standard which won’t go away:

HP-UX and I think others:
ON REAL(8) ILLEGAL CALL err(107,“Illegal REAL(8) value”)
!
OpenVMS
OPEN(1,STATUS=‘UNKNOWN’,ORGANIZATION=‘INDEXED’, &
FORM=‘UNFORMATTED’,RECL=20,KEY=(1:4:REAL), &
RECORDTYPE=‘FIXED’,FILE=‘istest1.dat’)

So, in handling all of Fortran, REAL is a declaration keyword, an intrinsic function, an auxiliary keyword and a qualifier. This isn’t the only one. I now know why it took so long to write the keyword handler in fpt :wink:

1 Like

Right, but this one is less ambiguous. The first form is clearly a declaration, while the second form is clearly an executable statement. In contrast, the two different usages of TYPE would look highly similar, forcing the the reader of a code to search if the enclosed name is a type name or a variable name.

A related question is actually “why do we need to mention type() to declare a type?”.
sometype_t :: a may be allowed instead of type(sometype_t) :: a
Then using type(x) instead of typeof(x) would be less ambiguous.

But I’m afraid anyway it’s too late now to change all of this, as it would introduce some confusion (and it’s not a critical issue of the language IMO).

1 Like

One thing that’s obvious in this thread, is the thought of “less is better”, clearly derived from languages whose syntax is borrowed from C —e.g., the function|func|def keyword is not in C, or C++, so visual parsing requires multiple passes just to know where you are (the inline keyword is probably the only one that clearly indicates a function).

Where C was designed from the point of view of the compiler (no function keyword but a hundred ways to assign things and it even had a register keyword), Fortran was designed from the point of view of the user/programmer (likely one who already holds an advance degree in something else), so being as explicit as possible is always better.

Even if type(x) and typeof(x) are obvious to the compiler, they might not be so for the programmer. You can even say type(integer) if it makes more sense to you.

It’s like that proposed syntax for simplified templates having ^ for the sole benefit of the programmer, not the compiler.

Maybe we could introduce a keyword KINDA(x) that returns TRUE for roughly similar values or types.

if (y == kinda(x)) then
   print *, "Eh, close enough!"
end if

:upside_down_face:

4 Likes

You meant the other way round? I can’t see any benefit to the programmer.

1 Like

Yes. These recent additions to the language come from the Fortran committee process, which didn’t include public discussion about these features, nor a compiler prototype and asking users to try it out and provide feedback. I tried to open up the committee around 2020, you can see as a reply to a public thread that I started and the typeof was discussed a bit here: October 2020 WG5/J3 meeting · Issue #185 · j3-fortran/fortran_proposals · GitHub. I think these kinds of discussions really help, and even more should be done (compiler prototype, etc.) and especially before things get standardized, not after. I encourage the committee’s leadership to resume such public discussions for all papers before they get passed. :slight_smile:

4 Likes

I suspected this.

In the late 1980s to early 1990s I worked with a small team on the language development of ADSIM, a domain-specific language for real-time continuous system simulation. For any new feature our ground rules were:

  1. We canvassed the user group to see what they wanted
  2. We prototyped the compiler
  3. We ran the prototype compiler on our internal libraries of applications to see whether we had broken anything
  4. We let a few users try it out.

This for a language used at less than a hundred sites and maintained by about a dozen people. Surely we can do this for Fortran?

3 Likes

Exactly right. Not only we can do this, we have to do this.

But we will, we have already prototyped several features in LFortran and it’s actually a lot of fun and once we can compile all codes, I am hoping the community will help with prototyping new features. I am also hoping other compiles (Flang, GFortran and others) will do the same. In fact they did with the unsigned prototype already: Unsigned integers · Issue #2 · j3-fortran/fortran_proposals · GitHub, although I personally don’t agree with this particular design, but I am super happy they prototyped what they thought is the best design. Now we can test it out, provide feedback, later on I am hoping to prototype what I think is a better design, and we can have these discussions and only then we can standardize something. We just have to do it for all features, and the committee leadership should require that. :slight_smile:

4 Likes

@certik - I am very happy that progress has already been made!

We can also prototype new constructs in fpt. fpt isn’t a compiler, but it supports most of the language extensions made since FORTRAN 77. Adding anything new will expose collisions with Gould-SEL, HP3000, VMS, HP-UX and other extensions. All of these are still out there, and, by the way, some of them contain lessons that the Standards Committee have missed. We can also automate translations backwards and forwards between new constructs and current standards where this is possible. We welcome the challenge!

1 Like

@Jcollins excellent. You can look at some of the papers that the committee has passed for the next standard and try to prototype them. Those by default will become part of the standard anyway, so you might as well add the support now and if there are issues, at least we’ll find out early.

To declare it is necessary, but it is not necessary everywhere. In an allocate statement one does allocate(sometype_t :: a).

And yet you link to public discussion of the features - that’s what the fortran_proposals Github was for, wasn’t it? It’s not as if these proposals were made in secret - everything is out in the open on the J3 website.

Personally, I prefer the TYPEOF and CLASSOF spellings as I find them clearer and less ambiguous to the reader. I find overloading of keywords to be confusing.

1 Like

Yes, exactly. You should embrace it more. :slight_smile:

Forgive me - I didn’t mean to start an argument.

Let me explain the context of my original question.
Fortran is a wonderfully powerful language but the syntax, scarred by 70 years of evolution, is highly irregular. For example:

i. the attributes of a FUNCTION declaration form a space-separated list before the keyword FUNCTION. The attributes of a variable declaration form a comma-separated list after the keyword. -
INTEGER RECURSIVE FUNCTION foo(bar)
INTEGER,PARAMETER,DIMENSION(3) :: thing

ii. Some keywords are followed by parenthesised arguments, some are not:
ALLOCATE(character(len=i3) :: c16,STAT=istat)
SELECT CASE (i)
CYCLE i_loop
DO i=1,3

iii. Some keywords have a mixture of parenthesised and non-parenthesised operands:
WRITE(*,‘(4I8)’)ia
GOTO (1001,1002,1003,1004)n (I know - not supposed to do that)

To write TYPEOF(x) but KIND(x) is yet another inconsistency.

A problem is that if you write Fortran every day you don’t see the irregularity of the syntax - you are (hopefully) thinking about the problem you are trying to solve. But put yourself in the position of an experienced programmer in some other language. In an earlier life I was an experimental psychologist. If you really want to screw up a cognitive task impose an additional irrelevant memory load on it.

A proposal: We work out what a regular Fortran syntax might look like and then create alternative ways of writing non-conforming statements. We shouldn’t, and can’t delete what we already have but DECODE/ENCODE died for good reasons and some of the existing oddities might eventually follow them.

BTW, given the current enthusiasm for GO TO instead of GOTO, shouldn’t we write TYPE OF instead of TYPEOF and IN OUT instead of INOUT :face_with_raised_eyebrow:

This is one of the reasons I’ve advocated making the CALL keyword optional for referencing SUBROUTINES with the following restrictions. Its only allowed when:

  1. There is an explicit interface via a module or local interface block visible to the compiler
  2. The routine is explicitly defefined as an external routine in an EXTERNAL statement.

In the absense of these two conditions the old rules about CALL apply. This idea came to me when I tried to get a very bright graduate student who knew Python and some C++ up to speed on a Fortran code I wanted him to use in his research. One of the first questions he asked was why was prepending CALL to a subroutine reference needed. He didn’t have to do that in Python or C++. The best answer I could give him was because that is the way its been done for 50 years and no one has questioned why its still needed. Also, I use INOUT all of the time but most books I’ve seen actually use IN OUT.

Why is void required to define a C/C++ function that returns nothing? Why is the explicit inclusion of so many header files is required in C/C++ just to use functions that are part of the language? Many things can be questionned in all languages.

Absolutely, but what’s the point of renaming things that have been standard for decades just because we’ve reconsidered the name?