[comp.lang.fortran] LABEL data type

wws@raphael.cray.com (Walter Spector) (03/08/91)

In article <91066.151240LJM@SLACVM.SLAC.STANFORD.EDU>,
LJM@SLACVM.SLAC.STANFORD.EDU (Len Moss) writes:
> [ ... stuff on convenience and efficiency of ASSIGN ... ]
> 
> I don't know why Mr. Maine considers ASSIGN poor style, but the reason
> I object to it is that it confuses what should be two entirely separate
> data types, namely INTEGER and "statement label".

:-)

I can see where ASSIGN could be used for backtracking!

Labels are an area where various Fortrans implementations are really wierd,
and Fortran-77 actually made matters worse (with alternate returns)!
I've wondered about this topic in the past too.  Consider some of the
various uses of statement labels:

	- You can ASSIGN them to an integer

	- You can use them as constants in a variety of places

		- GOTO label

		- GOTO (label1,label2,...), i

		- IF (something logical) label1,label2,label3

		- CALL sub (*label)

		- READ/WRITE(unit,label) and PRINT label

		- END=label,ERR=label in I/O statements

	- You can use integers containing labels:

		- READ/WRITE(unit,intlabel)

		- GOTO intlabel [[,] (label1,label2,...)]

		- READ/WRITE(unit,intlabel)

	- The alternate RETURN mechanism -

		- CALL sub (*label)

		- SUBROUTINE sub (*)

		- RETURN n

There is no type checking, so the following has obvious problems:

	assign 100 to mylabel
	yourlabel = mylabel
	newlabel = yourlabel
	goto newlabel

(bringing back memories of Hollerith constant problems.)


There are places where only labels themselves can be used.  Sometimes
you are referring to the label as '100' and sometimes '*100'.
In theory all places where labels can be used could allow label
variables.  I have even seen a compiler (Univac 1100) which allowed
'&100' (and you could use it in a DATA statement.  You could even
use ASSIGNed integer variables in 3-branch IFs and computed GOTOs!)

On some systems, you can pass label values through routines and
(theoretically) jump from a deep nest all the way back to your main
program!  (Kids! - Don't try this at home!)  This obscurity could
actually give Fortran a setjmp/longjmp facility.  I think it
is non-standard to jump outside the current program unit (except
via alternate return) and would probably *really* screw up the stack...
CASE statements don't really replace ASSIGNed GOTO (as the Fortran-90
committee would have us believe.)  Maybe what's needed is a pair of
setjmp/longjmp intrinsic routines.

A LABEL data type would help document use of labels better.  Maybe, ASSIGN
*should* be the Fortran equivalent of 'setjmp' and assigned GOTO should
be the equivalent of 'longjmp'.  One might also like 'label constants'
such as '*100' (as used in CALL statements), but consider the confusion
in a DATA statement: 

	label mylabel(10)
	data mylabel/10**100/
or?
	data mylabel/10*(*100)/

Do you allow 'label constants' everywhere a label is allowed?

	go to *100
	go to (*100,*200,*300), i
	read (iunit,*20,end=*30)

(Kind 'o makes Fortran look like C, doesn't it?...)

Why should labels passed into a subroutine for alternate returns be
different than labels passed into a subroutine for an I/O statement?
E.g., the consider the following:

	program brain
	label junk1,junk2
	...
	assign 100 to junk1
	assign 200 to junk2
	call damage (junk1,junk2,*300,*400)
	...
   100	format (...)
   200	format (...)
	...
   300	continue
	...
   400	continue
	...
	end
	subroutine damage (la,lb,lc,ld)
	label la,lb,lc,ld
	print la
	print lc
	if (something .or. another) then
		go to lb
	else if (something_else) then
		go to ld
	endif
	...
	end

What about 'type conversion' between old integer label variables and
new LABEL label variables (important for compatibility with existing
code.)

Since IF/ELSE/ELSEIF/ENDIF and character variables for formats was
introduced in Fortran-77, and now many vendors have implemented the
Mil Spec 1753 (and Fortran-90) DO/ENDDO and DO WHILE, labels are
being used far less than the old days.  With the rest of the new
Fortran-90 constructs (EXIT, CASE, etc.) the remaining valid uses
of labels will be the above 'wierd stuff'.  Maybe now is the time to
start thinking about getting it under control.

And of course, while we are on the topic of new data types, what
about EXTERNAL and INTRINSIC data types?  (And does it really make
sense for the Mil Spec routines to work on integers?  Maybe there
should be a CDC-style BOOLEAN data type for all that masking and
shifting of those old Hollerith variables!)  And what about making
IMPLICIT NONE the default for new source form?

:-)
	
Walt Spector
(wws@renaissance.cray.com)                       "Parity is for farmers"
Sunnyvale, California                                    - Seymour Cray
_._ _._ _.... _. ._.

jlg@lanl.gov (Jim Giles) (03/09/91)

From article <214949.21497@timbuk.cray.com>, by wws@raphael.cray.com (Walter Spector):
> [...]                              Maybe what's needed is a pair of
> setjmp/longjmp intrinsic routines.

No.  That leads to as many problems as it solves.  What's really
needed is a well designed exception handling mechanism.  Even
alternate return is a better solution than setjmp/longjmp (at
least alternate return maintains proper call chain protocols;
setjmp/longjmp are _supposed_ to be properly nested, but nothing
in either the syntax or semantics makes this constraint easy to
apply - and many implementations _don't_ apply it).

Frankly, I think that the trend to avoid labels and jumps altogether
is a better way to go.  I don't think that any language is really
complete without a GOTO, but as time goes on it may be less and
less of an issue.

J. Giles

LJM@SLACVM.SLAC.STANFORD.EDU (Len Moss) (03/09/91)

In article <17077@lanl.gov>, jlg@lanl.gov (Jim Giles) says:
>
>From article <214949.21497@timbuk.cray.com>, by wws@raphael.cray.com (Walter
>Spector):
>> [...]                              Maybe what's needed is a pair of
>> setjmp/longjmp intrinsic routines.
>
>No.  That leads to as many problems as it solves.  What's really
>needed is a well designed exception handling mechanism.

I agree.  At one point, Fortran 90 (well, 8x at the time) even contained
what I considered to be a very well-designed exception handling
mechanism, but it was removed in the interest of "reducing the size
of the language".  At the time, X3J3 talked about eventually publishing
such features in a "Fortran Journal of Development" as suggested
extensions.  Maybe now that Fortran 90 is just about done X3J3 will
follow through on this idea.

[Stuff omitted.]

>
>Frankly, I think that the trend to avoid labels and jumps altogether
>is a better way to go.  I don't think that any language is really
>complete without a GOTO, but as time goes on it may be less and
>less of an issue.

Perhaps the sign of a really good language is one which contains a
GOTO which no programmer ever uses ;-)

>
>J. Giles

--
Leonard J. Moss <ljm@slacvm.slac.stanford.edu> | My views don't necessarily
Stanford Linear Accelerator Center, Bin 97     | reflect those of SLAC,
Stanford, CA   94309                           | Stanford or the DOE

vsnyder@jato.jpl.nasa.gov (Van Snyder) (03/09/91)

In article <214949.21497@timbuk.cray.com> wws@raphael.cray.com (Walter Spector) writes:
>...
>Labels are an area where various Fortrans implementations are really wierd,
>and Fortran-77 actually made matters worse (with alternate returns)!...

Alternate returns are useful for exceptions: unlike a status flag, a lazy
user can't ignore them.  Fortran 90 HAD exception handling until the
"Halifax Compromise", where lots of neat stuff ended up on the cutting room
floor.

>...  Maybe there
>should be a CDC-style BOOLEAN data type for all that masking and
>shifting...

Another victim of the Halifax Compromise.

You should have written to X3J3 about three years ago.  Fortran 90 has been
through 3 public reviews, and those of us who agree with you have found
Fortran 90 to be emasculated.  However, the irregularity of the new language
definitely preserves the "beloved Fortran tacked-on look."

-- 
vsnyder@jato.Jpl.Nasa.Gov
ames!elroy!jato!vsnyder
vsnyder@jato.uucp