[comp.lang.fortran] Is this a correct Fortran 88 subroutine?

sjc@key.COM (Steve Correll) (09/06/89)

	SUBROUTINE X(L)
	LOGICAL L
	IF: IF ( L ) THEN
	    ELSEIF		! This is not an ELSEIF statement
	    ENDIF IF
	END
-- 
...{sun,pyramid}!pacbell!key!sjc 				Steve Correll

brainerd@unmvax.unm.edu (Walt Brainerd) (09/06/89)

In article <1018@key.COM>, sjc@key.COM (Steve Correll) writes:
> Is this legal Fortran 8x?
> 
> 	SUBROUTINE X(L)
> 	LOGICAL L
> 	IF: IF ( L ) THEN
> 	    ELSEIF		! This is not an ELSEIF statement
            ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> 	    ENDIF IF
> 	END

It doesn't look like legal anything to me.  Guess I don't understand the
question.  The rest of the subroutine looks OK.

-- 
Walt Brainerd  Unicomp, Inc.           brainerd@unmvax.cs.unm.edu
               2002 Quail Run Dr. NE
               Albuquerque, NM 87122
               505/275-0800

bleikamp@convex.UUCP (Richard Bleikamp) (09/06/89)

In article <1018@key.COM> sjc@key.COM (Steve Correll) writes:
>
>	SUBROUTINE X(L)
>	LOGICAL L
>	IF: IF ( L ) THEN
>	    ELSEIF		! This is not an ELSEIF statement
 Yes, this is an ELSE stmt with an optional construct name (fixed source form)!
>	    ENDIF IF
>	END
>-- 
>...{sun,pyramid}!pacbell!key!sjc 				Steve Correll

On page 8-2 of version 112 of S8 (latest working document from X3J3)
the ELSE statement allows an optional "if-contruct-name" after the ELSE
keyword.  This is not ambiguous, and appears no more difficult to handle
in a lex than most other Fortran "keywords" in non-keyword contexts.
However, if you worked for me, and wrote code like this, I'd probably
fire you :-).  But seriously, keep trying to find any really ambiguous
situations caused by the new proposed standard.

------------------------------------------------------------------------------
Rich Bleikamp			    bleikamp@convex.com
Convex Computer Corporation	    

sjc@key.COM (Steve Correll) (09/07/89)

> > 	SUBROUTINE X(L)
> > 	LOGICAL L
> > 	IF: IF ( L ) THEN
> > 	    ELSEIF		! This is not an ELSEIF statement
>             ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> > 	    ENDIF IF
> > 	END

Is this an ELSE token followed by an optional if-construct-name "IF", or does
the standard prohibit that interpretation?
-- 
...{sun,pyramid}!pacbell!key!sjc 				Steve Correll

brainerd@unmvax.unm.edu (Walt Brainerd) (09/07/89)

In article <1024@key.COM>, sjc@key.COM (Steve Correll) writes:
> > > 	SUBROUTINE X(L)
> > > 	LOGICAL L
> > > 	IF: IF ( L ) THEN
> > > 	    ELSEIF		! This is not an ELSEIF statement
> >             ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> > > 	    ENDIF IF
> > > 	END
> 
> Is this an ELSE token followed by an optional if-construct-name "IF", or does
> the standard prohibit that interpretation?

This is a nice example of why I have been fighting putting construct names
on the ELSE and ELSE IF statements.  You can really construct some awful
looking stuff, but I had forgotten about it myself!

This would be perfectly OK using the old fixed source form, but I think
it is not legal in the new free source form.  The proposed standard says:
"A blank must be used to separate names, constants, or labels
from adjacent keywords, names, constants, or labels."  ELSE is a keyword
and IF is a (construct) name.  (This is not offered as an excuse
for my goof.)  If you put a blank between ELSE and IF, it would be legal
in both forms, so your point is still valid.

I don't think much of the readability of the following either:

COMPUTE_TAX:  IF (INCOME < 1000) THEN
                 TAX = ...
              ESLE IF (INCOME < 5000) THEN COMPUTE_TAX
                 TAX = ...

The construct name looks like a branch back to the IF statement or
a procedure call or something to someone not experienced with Fortran 8x.
In short, it doesn't seem to say what it is doing.  Bracketing an IF
construct with a name on the IF and again on the END IF I think is
a great idea, however.
-- 
Walt Brainerd  Unicomp, Inc.           brainerd@unmvax.cs.unm.edu
               2002 Quail Run Dr. NE
               Albuquerque, NM 87122
               505/275-0800

hallidayd@yvax.byu.edu (09/08/89)

Steve Correll (sjc@key.COM), as per your message (<1018@key.COM>) concerning
the legality of the construct

>        SUBROUTINE X(L)
>        LOGICAL L
>        IF: IF ( L ) THEN
>            ELSEIF              ! This is not an ELSEIF statement
>            ENDIF IF
>        END

in Fortran 8x --- the answer is YES in fixed form, where blanks are not
significant; NO in free form, where a blank would have to appear between the
ELSE and IF in the marked statement (even if the blank were inserted, the
statement would be no less confusing to the human reader).  See syntax rules
R802 to R806 (section 8.1.2.1, p. 8-2), along with the syntax rule, R801, for
block  (section 8.1, p. 8-1) which alows empty blocks.  This _may_ show a
``failing'' in the way the if-construct-name is alowed to be used in
Fortran 8x.  This construct is still unambiguous, by the syntax rules, since
an  else-if-stmt  must include `(scalar-logical-expr)THEN', which the above
does not, however, this is a confusing construct for the human reader.

The question is: if the syntax alows all legal constructs to be parsed
unambiguously, is it necessary for the syntax rules to exclude all constructs
which can be confusing to human readers, regardless of how contrived such
constructs may be?

   _____________________________________________________________________
  / David Halliday                                                      \
  |                                                                     |
  | Internet:    hallidayd@yvax.byu.edu  or  hallidayd@acoust.byu.edu   |
  | BITNET:      hallidayd@byuvax  or  hallidayd%acoust.byu.edu@utahcca |
  | Us Mail:     BYU Physics Department                                 |
  |              296 ESC                                                |
  |              Provo, UT  84602                                       |
  \_____________________________________________________________________/

mccalpin@masig3.ocean.fsu.edu (John D. McCalpin) (09/09/89)

In message <14040@lanl.gov> jlg@lanl.gov (Jim Giles) writes:
>I have always favored a syntax in which block names _always_ appear
>on the left:
>        IF: IF( L ) THEN
>           ...
>        IF: ELSE
>           ...
>        IF: ENDIF
>Here, the visual ambiguity is gone (there never was any computational
>ambiguity).... [ etc ]

I prefer putting the construct names on the right, but separating them
with a colon, as in

	label: IF ( L ) THEN
	    statement 1
	ELSE: label
	    statement 2
	ENDIF: label

Of course, in the new syntax, you are free to use a ! between the
ELSE/ENDIF and the label to remove any visual ambiguity, but this
approach allows the labels to provide info to the compiler --- as
could be required for CYCLE and EXIT statements inside nested loops.

I think I made some comment about this in my formal response to the
original proposed draft --- but that was so long ago that I can't
remember....
--
John D. McCalpin - mccalpin@masig1.ocean.fsu.edu
		   mccalpin@scri1.scri.fsu.edu
		   mccalpin@delocn.udel.edu

jlg@lanl.gov (Jim Giles) (09/09/89)

>        SUBROUTINE X(L)
>        LOGICAL L
>        IF: IF ( L ) THEN
>            ELSEIF              ! This is not an ELSEIF statement
>            ENDIF IF
>        END

I have always favored a syntax in which block names _always_ appear
on the left:

        IF: IF( L ) THEN
           ...
        IF: ELSE
           ...
        IF: ENDIF

Here, the visual ambiguity is gone (there never was any computational
ambiguity).  Some people regard this is ugly, but if the purpose
of block names is as a documentation aid as well as a flow control
aid, then this syntax serves the purpose well.  All the block names
are easier to find on the left and will line up on properly indented
code.  Here is an example with loops:

        LOOP: DO I=1,1000
              ...
        LOOP: EXIT IF (COND)           !EXITS CAN BE CONDITIONAL
              ...
        LOOP: EXIT                     !OR UNCONDITIONAL
              ...
        LOOP: END DO

Of course, CYCLE and CYCLE IF statements are also possible.  Note the
with the block name on the left, there is never any doubt about which
statements on the page have a flow control effect - and no doubt about
which construct they belong to.  With the block names on the right,
they are effectively buried in the middle of the program text.