Interactive Fortran, LFortran, IDL, GDL and a question about structures

Dear all,

From time to time I hear about attempts to make Fortran interactive one way or another, or to create some interpreter version of the language. Do you know what’s the status of these efforts? Is LFortran something to bet on in the future?

I am doing visualization and postprocessing in IDL (Interactive Data Language, proprietary language/program by Harris Geospatial, https://www.l3harrisgeospatial.com/Software-Technology/IDL) that has its opensource clone GDL (https://github.com/gnudatalanguage/gdl). The biggest issue is the price of the license for IDL that turns away more and more scientific institutes pushing the researchers and mainly the students towards alternatives (“alternatives” actually == python).

The syntax of IDL is fairly similar to Fortran making it almost trivial to translate relatively simple codes (both are are strongly array-oriented, actually I believe that IDL was in the early days very much inspired by Fortran). Does anyone here has experience with it? Would it be possible to think of some hybrid between Fortran and IDL/GDL? What I mean is “an IDL/GDL version that follows fortran syntax even more closely”? Is there a contact between the GDL and LFortran communities?

Partly unrelated: Elements (tags) of a structure in IDL are defined in a similar way as in Fortran, using “.” instead of “%”. If I have array of structures, then I can assign values to an element of array as

a[i] = {var1 : 0, var2 : “whatever”, tag3 : 0.D0}

Is there a way to do this in similar way in Fortran or one needs to do lengthy:
a(i)%var1 = 0
a(i)%var2 = “whatever”
a(i)%tag3 = 0.D0

Best,
Niko

2 Likes

Hi @Niko,

Thanks for the post. I’ll answer some of your questions:

I am the author of LFortran, so I can only speak for myself: I bet on it about 3 years ago, and it has been my main effort every since. It’s a lot of work, but we are getting there. It’s still a pre-alpha status, meaning it is not ready for serious use, but it is now getting really close. If anyone wants to help, please let me know! I am looking for volunteers. The best way anyone can contribute is to help me figure out a roadmap of the first things to get working to get first users. Simple programs compile, but we need to get enough features in to get useful. The design itself is pretty much done, it compiles to binaries, it is interactive, it is very fast (to compile) and the design seems robust and clean.

I think there is no doubt it will bring more users to Fortran and it will allow Fortran to be used in ways previously not possible. By itself it cannot fix all problems with Fortran, and thus all our other efforts: website, fpm, stdlib, standards committee incubator repository, etc.

Does anyone here has experience with it? Would it be possible to think of some hybrid between Fortran and IDL/GDL? What I mean is “an IDL/GDL version that follows fortran syntax even more closely”? Is there a contact between the GDL and LFortran communities?

Yes, I have some experience with IDL from about 20 years ago. Back then I decided that Python was a better bet that had a brighter future, so I have been mostly using Python for my interactive tasks and I have contributed to the Python ecosystem a lot.

One can think of any combination of the mentioned languages, including also Matlab and Julia.

However, when it comes to performance, Fortran is still doing very well, both in practice, as well as in terms of yet unrealized potential of Fortran as a language. That is why I decided to start LFortran, trying to make Fortran as interactive as possible, while staying true to its nature and compatible with it.

One can think of extending Fortran in various ways. That is why I joined the committee and have discussed with many. If you have ideas for that, feel free to open issues in the incubator repository I mentioned above and we can discuss the details.

It seems that most people agree to keep Fortran what it is, not trying to make it a language that does everything for everybody, but rather concentrate on high performance numerical computing, and try to make it the best language in that domain.

4 Likes

@Niko,

I assume you mean derived types in Fortran when you mention “structure in IDL”. If yes, do you have component initialization in your derived type(s) and have you tried the “structure constructor” facility in the language?

   integer, parameter :: MAXLEN = 10
   type :: t
      integer :: var1 = -1
      character(len=MAXLEN) :: var2 = ""
      integer :: var3 = -1
      double precision :: tag1 = -99.0D0
      double precision :: tag2 = -99.0D0
      double precision :: tag3 = -99.0D0
   end type
   type(t) :: a(3)

   a(1) = t( var1=0, var2="whatever", tag3=0D0 )

   print *, "a(1) ", a(1)

end

The following program can output

a(1) 0 whatever -1 -99.000000000000000 -99.000000000000000 0.0000000000000000

Thus, would something like this in Fortran be something you’ll be ok with?

a(1) = t( var1=0, var2="whatever", tag3=0D0 )
2 Likes

Many thanks for your reply, @certik! I hoped to find here someone who knows about LFortran, but getting the answer from its author is beyond expectations.

I’ve downloaded it today, installed it through conda quite smoothly on my Kubuntu machine and played a bit with it. It certainly looks as a very interesting project. Is there already a user manual or some document describing the details? How much is the syntax in the interactive mode now restricted? I wasn’t able to declare an array, for example -

integer, dimension(3) :: x
x = (/1, 2, 3/)
Segmentation fault (core dumped)

I am not sure if I can really help you with the roadmap. A tool that I’d wish to have would be something like IDL, but with Fortran-like syntax. :slight_smile: One of the reasons why people still use IDL is the huge amount of legacy code. If it would be possible to translate this code automatically/efficiently to Fortran that can be executed interactively, I believe that would win many hearts in the IDL community.

Thanks for the suggestion to contribute to the incubator repository. I will first check to see what is already there.

Ooooh, many thanks @FortranFan! Yes, derived types in Fortran are pretty much equivalent to structures in IDL. I use them quite extensively, but I never knew how to assign values to multiple tags in one line. The line

a(1) = t( var1=0, var2="whatever", tag3=0D0 )

is what I’ve been looking for. Many many thanks!!

(I’ve learned Fortran mostly on my own and along the way. Sometimes I am a bit ashamed of various holes in my knowledge. :slight_smile: )

It shouldn’t segfault, that is a bug. For me (in Debug mode) it prints:

>>> integer, dimension(3) :: x                                                  
>>> x = (/1, 2, 3/)                                                             
Other LFortran exception: visit_ArrayInitializer() not implemented

Which just means that I haven’t implemented an initializer yet. We will get to it soon.

1 Like

I have nto had time yet to read the entire thread, so I may be completely mistaken about the actual problem, but I have recently written a small module that allows a very basic type of interactivity in a Fortran program. That is:

  • It implements a read-evaluate-print loop
  • You can define commands that are associated with a routine
  • Only simple commands are possible (no variable substitution or the like or control structures)

It does work for the limited purposes I had in mind.

Here is an example:

  • It registers two commands, “setparam” and “print-table”
  • It invokes the read loop

! example_repl.f90 –
! Very simple example of using the REPL module
!
program example_repl
use repl

implicit none

real :: param

!
! Hm, we must first initialise the REPL module ...
! - would be nicer if we can hide that.
!
call init_repl

!
! Now register our specific commands
!
call register_cmd( "setparam", setparam, "Set the parameter value" )
call register_cmd( "print-table", print_table, "Tabulate the function - xmin xmax steps" )

call read_loop
! Use this for stored commands; call run_file( "example.run" )

contains

subroutine setparam( cmdname, arg )
character(len=*), intent(in) :: cmdname
type(arg_t), dimension(:), intent(in) :: arg

real                                  :: new_param
integer                               :: ierr
logical                               :: error

call check_number_arguments( cmdname, size(arg), 1, 1, error, ' new-value' )
if ( error ) return

call get_value( cmdname, arg(1), new_param, error )
if ( .not. error ) then
    param = new_param
else
    write(*,'(a,g10.3)') '- keeping old value ', param
endif

end subroutine setparam

subroutine print_table( cmdname, arg )
character(len=*), intent(in) :: cmdname
type(arg_t), dimension(:), intent(in) :: arg

real                                  :: x, xmin, xmax
integer                               :: i, steps
logical                               :: error

call check_number_arguments( cmdname, size(arg), 3, 3, error, 'minimum maximum number-of-steps' )
if ( error ) then
    return
else
    call get_value( cmdname, arg(1), xmin,  error ); if ( error ) return
    call get_value( cmdname, arg(2), xmax,  error ); if ( error ) return
    call get_value( cmdname, arg(3), steps, error ); if ( error ) return
endif

write(*,'(a,g10.4)') 'Function parameter: ', param

do i = 0,steps
    x = xmin + i * (xmax - xmin) / steps

    write(*,'(2g10.3)') x, func(x)
enddo

end subroutine print_table

real function func( x )
real, intent(in) :: x

func = cos( param * x)

end function func

end program example_repl

A bit more careful reading shows that OP is asking about a far more flexible feature than this module offers :slight_smile:

In the book Abstracting Away the Machine: The History of the FORTRAN Programming Language (2019) by Mark Jones Lorenzo, I discovered page 189 that the ancestor of LFortran is Quiktran: it was a timesharing system developed by IBM between 1961 and 1963, with debugging and terminal control facilities, especially a Fortran interpreter. You could type commands to test them, like nowadays with Python (or yesterday with 80’s BASICs).

It’s difficult to find more information on the net. There is some a the end of this paper “Approaches to conversational Fortran”, D.W. Baron, 1970: