Overloaded asterisk

Years ago I wrote a Fortran 95 fixed source form program that has 19 different uses of the asterisk *, compiles and runs. Below is a Fortran 2018 version with 23 of them. It compiles and runs, though the two compilers I tried, gfortran and ifort, both gave some warnings. Are there any uses of * that I missed?

C Program to show 23 ways Fortran uses the asterisk. Comments at ends of 
* lines mark uses of *, as here:    ! Comment line, * character in it.  (1,2)
C This program is valid Fortran 2018, but its fixed source form, alternate
C return, and declaration beginning character* are all obsolescent. Class(*) 
C was new in f2003, unlimited format in F2008, and type(*) and rank(*) in
C F2018. List-directed internal read, use of lower case, and comments that
C begin with ! are its only other features that were not valid Fortran 77.
      program test23stars
      character:: b,c,d='?'
      integer j,k,n(2)
      data j,k/2*0/                 ! repeated value in data            (3)
      call input(n,'2*4',b,c,d,*666)! repeated value in list-directed input, 
C                                   ! alternate return                  (4,5)
      write(*,'(2i2,1x,a)') n(1)*j, ! default output unit ! multiply    (6,7)
     *      n(2)**k,b               ! continuation line ! exponentiate  (8,9)
      stop
 666  print '(a)', ' * error in n'  ! in non-comment character string   (10)
      print '(*(i4))', n            ! unlimited format item             (11)

      contains

      subroutine input(n,a,b,c,d,*) ! dummy alternate return argument   (12)
      integer,intent(out)::n(*)     ! assumed-size array                (13)
      character,intent(in)::a*(*)   ! length selector ! assumed length
C                                        following variable name        (14,15)
      character*(*),intent(out)::b  ! length selector ! assumed length
C                                        following character keyword    (16,17)
      type(*),intent(in)::c         ! assumed-type                      (18)
      character(1),intent(in)::d(..)
      integer i
      character ch
      class(*),allocatable:: e(:)   ! polymorphic entity                (19)
      select rank (d)
      rank(*)                       ! rank selector                     (20)
      print "(a)",'This should not be printed!'
      end select
      read(a,*,iostat=i) n(1),n(2)  ! list-directed internal read       (21)
      if (i.ne.0) return 1
      print '(a)', 'Enter anything to continue.'
      read(*,'(a)',iostat=i)ch      ! default input unit                (22)
      write(b,'(i1)',iostat=i)666   ! writes '*' as 666 won't fit in i1 (23) 
      end subroutine input
      end program test23stars
4 Likes

And there I am, thinking bad of C and C++ for reusing symbols like * and & for so many purposes that I get lost even trying to imagine the first few …

Sadly, in 2023, most of our programming languages are syntactically limited by the keyboards of the 1950s, and in many cases (but not Fortran) by the properties of Dennis Ritchie’s workstation. However, I’d rather figure out the multiple meanings of * than program in Unicode ala APL.

I can’t help but thing of Buffalo buffalo Buffalo buffalo buffalo buffalo Buffalo buffalo - Wikipedia when I see programs like this. This one is far more readable though, and I think it’s a nice contribution.

You mention * for reading from standard output, but a new programmer will first use * to print or write to standard output.

A quick glance did not show NAMELIST groups and DATA statements, where it can be used as a repeat count similar to list directed input; but distinct uses IMO.

DATA is there, NAMELIST i/o is not. There is an example of integer i/o overflow, but maybe some floating point examples could also be included (there are several types).

@Harper haha, that’s awesome. Here is one for you: Some cryptic source examples.

My * program does write to standard output in the line that ends (6,7) but I shall have to think about NAMELIST and floating-point i/o.

Seeing them all together was a little startling even though I knew them. Finally got a chance to
look at it. I think this one deserves consideration:

  character(len=*),parameter :: arr(*)=['aA','bB','cC']   ! length and array size on parameter

This is sort of a toss-up for me …

  write(*,'(*(g0,1x))')[1,2,3]*2**2 ! array multiplication

Cannot decide if array multiplication versus scalar multiplication should be given its own due or not.

I just wanted to add the obvious, if you think * is overloaded/overused within fortran, then what is your opinion of parentheses? :slight_smile:

The unlimited repeat count in that format is another case, regardless of the scalar/array question.

OP has already covered this - item marked (11).

1 Like

Like many things, parentheses are a necessary evil. If you think Fortran needs too many of them, keep away from Lisp.

Lisp is the second-oldest programming language, only three years younger than Fortran.

Lisp is not the second-oldest programming language: Plankalkul 1944-1945, Laning and Zierler system 1952, Fortran 1957, Algol 58 1958, Cobol 1959, Lisp and Algol 60 1960. (Sorry I don’t know how to put an umlaut on u in Fortran Discourse.)

I guess I needed more qualifiers in my statement. from Lisp (programming language) - Wikipedia

“Originally specified in 1960, Lisp is the second-oldest high-level programming language still in common use, after Fortran.”

1 Like

You could use the “e” to express an umlaut with basic ASCII: Plankalkuel. (Though I guess my keyboard does allow me to write Plankalkül directly …)

Thanks to @RonShepard and @urbanjost my test23stars program has grown to test29stars. Here is the new version, with a little tidying up.

C Program to show 29 ways Fortran uses the asterisk. This program is valid
C Fortran 2018, but its fixed source form, alternate return, and declarations
C beginning with character* are all obsolescent. Namelist first appeared in
C the F90 Fortran standard, class(*) and namelist with internal access in
C F2003, unlimited format in F2008, and type(*) and rank(*) in F2018. All the
C other uses of * were already in F77. though namelist I/O was an Oracle
C extension to F77 with a slightly different syntax.

      program test29stars
* Comments mark uses of * , as here:! Comment line, * character in it.  (1,2)
      character(2):: c,d='?'
      character(10):: b(4),ch
      integer j,k,n(2)
      data j,k/2*0/                 ! repeated value in data            (3)
      call input(n,'2*4',b,c,d,*666)! repeated value in list-directed input, 
C                                   ! alternate return                  (4,5)
      write(*,'(2i2,1x,4a)') n(1)*j,! default output unit ! multiply    (6,7)
     *      n(2)**k,' '//b          ! continuation line ! exponentiate  (8,9)
      stop
 666  print '(a)', ' * error in n'  ! in non-comment character string   (10)
      print '(*(i4))', n            ! unlimited format item             (11)

      contains

      subroutine input(n,a,b,c,d,*) ! dummy alternate return argument   (12)
      integer,intent(out)::n(*)     ! assumed-size array                (13)
      character,intent(in)::a*(*)   ! length selector ! assumed length
C                                        following variable name        (14,15)
      character*(*),intent(out)::b(:)! length selector ! assumed length
C                                        following character keyword    (16,17)
      type(*),intent(in)::c         ! assumed-type                      (18)
      character(2),intent(in)::d(..)
      integer:: i,nl(6)!!!=42
      integer,parameter:: e(*)=[1,2]! implied-shape array               (19)
      character(18)::nlin='&nlstuff nl=6*666/'! repeat in namelist input(20)
      namelist/nlstuff/nl
      class(*),allocatable:: f(:)   ! polymorphic entity                (21)
      read(nlin, nml=nlstuff)
      write(6, nml=nlstuff)         ! repeat in namelist output         (22)
      select rank(d)
      rank(*)                       ! rank selector                     (23)
      print "(a)",'This should not be printed!'
      end select
      read(a,*,iostat=i) n(1),n(2)  ! list-directed internal read       (24)
      if (i.ne.0) return 1
      print '(a)', 'Enter anything to continue.'
      read(*,'(a)',iostat=i)ch      ! default input unit                (25)
      write(b(1),'(i1)',iostat=i)42 ! integer output * if too big       (26) 
      write(b(2),'(f2.0)',iostat=i)42.0     ! real output * if too big  (27) 
      write(b(3),'(e10.4e1)',iostat=i)42e-20! real output * if too small(28)
      write(b(4),'(e8.4)',iostat=i)42.0     ! real output, bad format   (29)
      end subroutine input
      end program test29stars
1 Like