Syntax of interactive Fortran

LFortran can compile a Fortran source file as other compilers do, but for interactive use it allows some extensions that one would expect in an interpreted language. You can enter an expression such as 2+3 instead of print*,2+3. You don’t need an end program foo statement to have a script run. You can redefine a function.

Here are some thoughts on how it should work. I wonder what others think.

Currently you must declare variables before using them. For interactive use, I suggest that LFortran infer the type of a variable from its first use. You could write i = 2 and later i = 3.1, but i would already have type integer and would thus be set to 3. Writing i = "dog" would be illegal.

Should the call statement for invoking a subroutine be made optional for interactive use? Then foo() and call foo() would be equivalent.

If you have some code stored in a file, is there a way to load it in an interactive session?

Could LFortran save an interactive session as proper Fortran code? You could write a**2+b**2 during the session, but the saved code would be print*,a**2+b**2 . A literal transcript would also be fine – a transpiler could be written to convert the transcript to legal Fortran.

Could there be a command to list the names and values of all defined variables and parameters?

5 Likes

I have been thinking about this for a while, since before I knew about LFortran. Original fortran syntax is too verbose to effective interactive use. We need a whole lot of syntactic sugars to fasten typing. Editor plug-ins can be constructed to expand them into full standard complying code while saving into a file.

I agree with your suggestion on type inference. I had even suggested limited revival of first letter based inference of names as a Fortranly solution, e.g. istart or nstart should be an integer, while astart should be real.

It did not occur to me that `call’ is not necessary for distinguishing subroutines from functions.

Some other suggestions are fn for function and sub for subroutine. Ineference of intent should also be given a thought.

1 Like

Right, on a technical level all of these can be done. The question is more “what do we want”?

For now, LFortran is conservative and only does the minimal change to regular Fortran. Regular Fortran has a global scope that allows a program, modules, submodules, functions, subroutines (and also a common block and I believe a data block). LFortran extends this to also allow:

  • Statements (use statement, declarations, regular statements that you can use in the body of a function such as assignment, subroutine call, open statement, etc.)
  • Expressions (such as 2 or 2+3 or a function call)

I think that’s it. This simple change suddenly allows to use Fortran interactively. If you leave an expression at the end of a cell, it will get printed. This is also the minimal change. If you don’t allow expressions, it will be quite limited, as you can’t use it as a calculator. If you don’t allow statements, it’s going to be tough also (how do you declare a variable or assign to it?). So you at least have to do that. By only doing that, we are not closing any doors, we can always do more in the future without breaking people’s interactive notebooks.

However, this can be extended in many ways:

  • Infer the type of a variable from the RHS
  • Potentially use implicit typing, but that has issues, such as dimensions and other attributes that can be inferred from RHS
  • Not require call
  • Shorten the Fortran syntax in any possible way. For example, I was going to experiment with keeping the exact Fortran semantics, but totally change the syntax, such as using Rust style syntax. It’s doable. The question is, do we want this?

Now, being an ahead of time compiler means LFortran will parse this to AST and transform AST to ASR. Once in ASR, it is indistinguishable from regular Fortran (except the loose statements and expressions at global scope), so it is indeed possible to transform back to regular Fortran. Even the loose statements and expressions can be put into subroutines.

In practice, that can look as easy as:

%%show_fortran
a = 5.d0

And LFortran will print as the cell output the transformed code:

subroutine interactive_prompt_1()
integer, parameter :: dp = kind(0.d0)
real(dp) :: a
a = 5._dp
end subroutine

Or something like that. Then you can take it and do something with a.

So that can all be done. I welcome any suggestions. For now, we are just doing the minimal approach. Note that even the minimal approach is not too bad at all — even for interactive use. I quite like it. And as I said above, we can still do a lot more. Just keep brainstorming.

5 Likes

How would this work with type inference? If i has not been declared, I think i = 1.2 should set i to 1.2, not 1, and that i should have type real.

The suggestion was an alternative solution, rather than being complementary.

Note CALL is needed in regular Fortran because of its lack of reserved key words. While

    call case(i)

can be well defined, the lack of CALL and reserved keywords will make it difficult to process

    case(i)
2 Likes

LFortran already parses both the select switch as well as case(i) as well as an expression of a function call case(i). The relevant part of the parser is here: src/lfortran/parser/parser.yy · 0560216338467b55d53902ee01ec63e4c2117cc8 · lfortran / lfortran · GitLab :

    | statement          %dprec 7
    | expr sep           %dprec 8

So it adds precedence to a function call first in this case. However, if it can be parsed as a select case, it will be.

In general, in interactive mode you can encounter some ambiguities. and it seems you can always workaround them in some way. The ambiguities do not happen for regular code.

So on a technical level, the compiler can implement calling subroutines without call.

1 Like

For whatever it’s worth, I would prefer working interactively with Fortran to mean - at a high level - simply a REPL of standard Fortran statements that builds upon each prior evaluation.

To me, ideally 2+3 would be as meaningless in interactive work with Fortran as it will be now with the current paradigm. Whereas print *, 2+3 seems perfectly amenable to REPL.

Any syntactic shortcuts or syntactic changes of any kind relative to the standard, however trivial they may appear to creators, risk fragmentation of the language or seeding a pidgin. I personally would stay away from it.

4 Likes

In the context of my comment above, it seems instead of allowing both statements and expressions at the global level, you would only allow statements. And you would use print *, expr to print an expression expr. I think that would also work and that would actually be the minimal change. I haven’t thought of that.

1 Like

Maybe LFortran could have an option to be started in a standard conforming mode where only valid Fortran statements are allowed (so no bare expressions or omissions of “call”), but I hope that the mode allowing shortcuts is not removed. Typing an expression at the prompt is the first thing a new user will try, and I think it should just work, as it does now.

4 Likes

If one’s goal is to create a pidgin that “kinda” feels like Fortran, sure it’s a free world out there, one can always copy and tweak using countless number of other interactive environs to create yet another mutated clone. I personally do not think that will be good for Fortran.

2 Likes

IMO as long as there is an option to export the notebook to a fully compilable Fortran source, accepting some flexibility is fine. The standard accuracy of the code is a quality for the final product, but not so for prototype. More than that, it won’t be bad for Fortran is the prototyping environment is more relaxed and allows better expressivity, whenever a clearer correspondence to standards can be kept.

3 Likes

It looks like we can pretty robustly parse statements and expressions at the global scope with the current parser. So indeed, we can then enable rejecting expressions in the AST->ASR transformation, so if you start LFortran with an option, it will only allow statements. And we can keep the current parser that we have.

I think we just need to play with this. I don’t know what I would like myself. The logical progression of making Fortran interactive thus is:

  1. Regular Fortran. Global scope allows program, modules, procedures, common block, data block

  2. In addition to 1), also allow statements at global scope. That means use statements, declarations and any statement that you can put in a procedure or main program body.

  3. In addition to 2), also allow expressions at global scope.

  4. In addition to 3), also allow some other simplifications, such as inferring variables from RHS, maybe not require call, etc.

Right now LFortran does 3), but we can easily revert to 2) or make it configurable.

Indeed, as @lmiq said, we need an option to export the notebook to a fully compatible regular Fortran source code. And that should allow us to experiment a bit with different approaches.

Let’s keep the options open. I am happy to prototype things and we can test them out and see what we would like.

2 Likes

FWIW here’s what I’d like for interactive LFortran mode:

  • Allow statements at global scope (outside of program units)
  • Allow declarations to follow executable statements
  • Allow expressions as statements
  • Call subroutines without the call statement, like functions. Combined with the bullet point above, now we realize that Fortran doesn’t need subroutines at all, only functions.
  • Inferred typing by default; change to enforcing explicit typing (assume implicit none) with a switch; change to standard Fortran with a switch;
  • Statement functions (I believe this was standard F77)

To be brave and liberal at implementing various extensions and supersets of Fortran is LFortran’s greatest potential advantage IMO. Sure, support compiling standard Fortran with a switch, but don’t hold back with experimenting and pushing the language design beyond its limits.

1 Like

Since functions can return arrays and derived types, there is less need for subroutines than there used to be. But it’s good to have subroutines for operations such as random number generation or I/O that are not pure, or when you want to return an error flag.

In his keynote, @rouson advised

Write software.
Not too much.
Mostly pure functions.

but he did not say to avoid subroutines entirely. He mentions using them for assertions.

1 Like

The other frequently cited reasons to use subroutines is for faster return of arrays (possibly allocatable). However, the compiler optimizer should be able to optimize this out (for example by effectively transforming functions to subroutines internally, which is what LFortran does if an array is returned). So I think this is not a reason anymore.

The only real reason for subroutines is if you return more than one argument. This happens for eigensolvers that return eigenvalues and eigenvectors. So those are best served by subroutines.

I didn’t write that subroutines should be avoided. I think they can be useful, mostly to signal to the programmer that some work is about to be done that doesn’t fit the context of an expression.

I wrote that if you allow an expression as a statement and not require a call to invoke subroutines, e.g.:

integrate(f, x, t)

integrate could be defined as either a function or a subroutine. You can’t tell which one it is by just looking at the invocation, because it is both a statement and an expression. I think it doesn’t even matter whether it’s a function or a subroutine.

Functions can return arrays as fast as subroutines, just make those arrays intent(inout) or intent(out) arguments. But then, such functions have side-effects and I don’t recommend them. Use a subroutine instead.

By the same mechanism as above, functions can output (I write “output” to avoid the problematic word “return”) multiple results as actual arguments. But, because functions can only be used in expressions, better to use subroutines.

So IMO the main difference between functions and subroutines boils down to communicating intent. And once you allow expressions as statements, that difference goes away. Do you really need subroutines for anything, then? The flip-side would be that when a function intended to be used outside of larger expressions (that is, as an expression statement) is used inside a larger expression, could lead to confusing code.

In a way, these two interactive features (expressions as statements and invoke subroutines without typing call) could lead to a smaller language that is easier to misunderstand, perhaps more like C.

1 Like

Another idea: allow more than one return value from functions. Then I think functions and subroutines would be equivalent (except intent(inout) arguments). For eigensolver:

lam, c = eig(A)
2 Likes

Maybe some sort of reactivity is interesting in a Fortran notebook? For example, if this is allowed, what should happen if the type of a variable is changed? Or if all types are changed by changing the definition of a type parameter?

The Pluto notebooks have two features that are interesting: the reactivity and the fact that the final file is “just” a regular code file with annotations. The reactivity introduces some constraints, like not being able to assign a value to the same variable twice. Maybe for some statements, like type declarations, this an interesting feature for LFortran as well.

That would allow declarations to appear at the end, for example. (The “inference” could add a declaration cell automatically at the end?). Alternatively the type declarations could be automatically generated in a hidden cell just above the first assignment of a variable, being explicit and possibly editable.

2 Likes

I often miss multiple return values from functions in standard Fortran. I wish it had it. Though this can be emulated using derived types, it’s quite cumbersome.

3 Likes