[comp.lang.fortran] Pointer examples and 8x

bill@ssd.harris.com (Bill Leonard) (06/17/89)

In article <6028@microsoft.UUCP> bobal@microsoft.UUCP (Bob Allison) writes:

   My second biggest problem is that it is an attribute.  Bill Leonard, in
   email to members of the committee complained that it was awfully difficult
   to use this form of pointers to insert items in a linked list (at least,
>  I think that was the example), a fairly common usage of pointers.  As I
>  recall, someone came back with a solution which was deemed "elegant" and
>  was implemented using recursion.  Ugh!  I just want to walk around
>  lists and stuff.  Bill, could you post the problem again and see if 
>  anyone else can come up with a solution which doesn't require retraining
>  everyone who has ever used pointers in any other language?

Okay, here are my examples.  I am wrote these in C, since that is the
language that both has pointers as a data type and is one I use on a
regular basis.  Please excuse any minor programming errors -- the point is
that 8x pointers cannot point to other pointers, nor can I have an array of
pointers.  I think these examples show why those two features are very
important.

NOTE: I know that you CAN implement these routines in 8x IF you make each
pointer be a structure whose only field is the pointer.  This is fine, if
your purpose is to obscure what the code is doing.  Also, there is a very
good reason for only using _ONE_ pointer in the update example, rather than
two: it is much more efficient.  Any computer-science freshman can do it
with two!

Example 1: Updating a linked list.

struct list_element {
   struct list_element    * next ;
   int                      data ;
} * list_header ;

/* Routine delete removes a given element from the list. */

delete (key)
int     key ;
{
   struct list_element    ** update_ptr ;  /* Pointer to the next field
                                              to be updated when an element
                                              is deleted.
                                           */

   update_ptr = &list_header ;
   while (*update_ptr != NULL) {
      if ((*update_ptr)->data == key) {
         /* The list pointer pointed to by update_ptr now needs to
            point to the following element.  Note that this works
            even if update_ptr is pointing to the list header.
         */
         *update_ptr = (*update_ptr)->next ;
         return ;
      }
      update_ptr = &(*update_ptr)->next ;
   }
}

/* Routine insert inserts a new element before a given one.  Assume
   the macro NEW allocates a new list element.
*/

insert (newkey, inskey)
int     newkey ;         /* New key-value to insert. */
int     inskey ;         /* Key value of element that should immediately
                            succeed the new one.
                         */
{
   struct list_element    ** update_ptr ;  /* Pointer to the next field to
                                              be updated when the new
                                              element is inserted.
                                           */
   struct list_element     * new_element ; /* New list element pointer */

   update_ptr = &list_header ;
   while (*update_ptr != NULL) {
      if ((*update_ptr)->data == inskey) {
         /* The list pointer pointed to by update_ptr now needs to
            point to the new element.  The new element's next field
            needs to point to the element formerly referenced by
            *update_ptr.
         */
         new_element = NEW() ;
         new_element->data = newkey ;
         new_element->next = *update_ptr ;
         *update_ptr = new_element ;
         return ;
      }
      update_ptr = &(*update_ptr)->next ;
   }
   fprintf (stderr, "Desired element not found\n") ;
   exit (1) ;
}

Example 2: Sparse matrix.

/* This is an example of implementing a sparse matrix of integers.
   For simplicity, I show only the insertion routine, and I have
   assumed the number of rows is fixed.  In many cases, the number
   of rows would be dynamic, and so the array of row-pointers would
   be a dynamic array, itself referenced by a pointer.

   Each row element represents a range of consecutive integers, which
   may be only a single integer (if high==low).  The row elements are
   maintained in ascending order.
*/

struct row_element {
   struct row_element    * next ;
   int                    low ;
   int                    high ;
} ;

struct row_element   * (rows [NUM_ROWS]) ;  /* Array of pointers to row
                                               headers.  In 8x, this would
                                               have to be an array of
                                               structures whose sole
                                               element is a pointer.  That
                                               introduces a lot of
                                               syntactic baggage that
                                               obscures rather than
                                               illuminates.
                                            */

/* Routine insert inserts a new element into the matrix, if it is
   not already there.  For simplicity and brevity, I have not implemented
   all the special cases possible.
*/

insert (row, col)
int     row, col ;
{
   struct row_element   ** insert_ptr ;  /* Pointer used for insertion. */
   struct row_element    * new_element ; /* Pointer to new element if needed */

   insert_ptr = &(rows [row]) ;

   /* Search for the place to insert. */

   while ( ((*insert_ptr) != NULL) &&
           ((*insert_ptr)->high < col) ) {
      insert_ptr = &(*insert_ptr)->next ;
   }
   if (*insert_ptr == NULL) {
      /* We reached the end of the list.  Create a new element. */
      new_element = NEW() ;
      new_element->next = NULL ;
      *insert_ptr = new_element ;
      new_element->low = col ;
      new_element->high = col ;
   } else if ((*insert_ptr)->low < col) {
      /* The element is already in the list.  Do nothing. */
      ;
   } else if ((*insert_ptr)->low == col+1) {
      /* Extend this element backward. */
      (*insert_ptr)->low = col ;
   } else {
      /* Create a new element and insert it. */
      new_element = NEW() ;
      new_element->next = *insert_ptr ;
      *insert_ptr = new_element ;
      new_element->low = col ;
      new_element->high = col ;
   }
}
--
Bill Leonard
Harris Computer Systems Division
2101 W. Cypress Creek Road
Fort Lauderdale, FL  33309
bill@ssd.harris.com or hcx1!bill@uunet.uu.net

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

In article <BILL.89Jun16132046@hcx2.ssd.harris.com>, bill@ssd.harris.com (Bill Leonard) writes:
> In article <6028@microsoft.UUCP> bobal@microsoft.UUCP (Bob Allison) writes:
> 
>    . . .  Bill Leonard, in
>    email to members of the committee complained that it was awfully difficult
>    to use this form of pointers to insert items in a linked list (at least,
> >  I think that was the example), a fairly common usage of pointers.  As I
> >  recall, someone came back with a solution which was deemed "elegant" and
> >  was implemented using recursion.  Ugh!  I just want to walk around
> >  lists and stuff.

> Okay, here are my examples.  I am wrote these in C ...  the point is
> that 8x pointers cannot point to other pointers,
> 
> NOTE: I know that you CAN implement these routines in 8x IF you make each
> pointer be a structure whose only field is the pointer.  This is fine, if
> your purpose is to obscure what the code is doing.

Well, I guess Bill didn't read the responses to his own queries
last time around, but maybe this will give others the opportunity to see
how it can be done in Fortran 8x.

I should be doing useful work instead of this, but I don't want to leave
the impression that all X3J3 members can't write programs in Fortran.
(although in this case, as opposed to C, I don't have a compiler to
test it on, so there is even more liklihood of some bugs).

First, note that there is no need for pointers pointing to pointers.
All pointers in the list processing examples (both Leonard's and mine)
point to structures.  Also, there are no structures whose only component
is a pointer.

To show the contrast between the C program Bill wrote, the "walk" around
version in Fortran 8x and the (Ugh!) elegant version using recursion
even more, let's not pick the particularaly simple example in Bill's
list insertion, but instead assume the list is to be maintained in
ascending order.  If, for example, we are to insert the number 17,
it must work if the list is empty, if all numbers are < 17, or if
all numbers are > 17.  In this example, you have to make an insertion
_before_ the node you find having a certain property. To do this,
I think even nonfreshman need two pointers (a trailing pointer is needed)
(but maybe someone else can do it with one)
and the empty list is either a special case (Bill just printed an error mesg)
or there must always be a dummy node in the list (I have arbitrarily chosen
the latter).  Here are the necessary declarations.

   TYPE NODE
      INTEGER :: VALUE
      TYPE (NODE), POINTER :: NEXT
   END TYPE NODE

   TYPE (NODE), POINTER :: LIST
   INTEGER :: NUMBER

Next is the code to initialize the list (to contain only a dummy node).

   ALLOCATE (LIST)
   LIST % VALUE = -HUGE (0)
   NULLIFY (LIST % NEXT)

Here is the program to insert NUMBER in order in the list
by "walking" thru the list.

   SUBROUTINE INSERT (PTR, NUMBER)

      TYPE (NODE), POINTER, INTENT (IN) :: PTR
      TYPE (NODE), POINTER :: TMP_PTR, TRAIL_PTR
      INTEGER, INTENT (IN) :: NUMBER

      ! "Walk" thru the list to
      ! determine where NUMBER goes
      TRAIL_PTR => PTR
      TMP_PTR => TRAIL_PTR % NEXT
      DO
         IF (.NOT. ASSOCIATED (TMP_PTR) EXIT
         IF (NUMBER <= TMP_PTR % VALUE) EXIT
         TRAIL_PTR = TMP_PTR
         TMP_PTR => TRAIL_PTR % NEXT
      END DO

      ! Insert into sublist
      ALLOCATE (TRAIL_PTR % NEXT)
      TRAIL_PTR % NEXT % VALUE = NUMBER
      TRAIL_PTR % NEXT % NEXT => TMP_PTR

   END SUBROUTINE INSERT

Others may be able to write a better version that does this,
because this is not my style.  Following is the (Ugh!) "elegant"
version.  This should be compared to the previous version, or to
one supplied by someone else, if they can provide a better one.
First is the code to initialize the list (no dummy node needed).

   NULLIFY (LIST)

Next, the subroutine.

   RECURSIVE SUBROUTINE INSERT (L, NUMBER)

      TYPE (NODE), POINTER :: L, TMP_L
      INTEGER, INTENT (IN) :: NUMBER

      ! If NUMBER goes here, insert it in new node
      IF (NUMBER <= L % VALUE) THEN
         ALLOCATE (TMP_L)
         TMP_L % VALUE = NUMBER
         TMP_L % NEXT => L % NEXT
      ! Otherwise, insert into sublist
      ELSE
         CALL INSERT (L % NEXT, NUMBER)
      END IF

   END SUBROUTINE INSERT

Challenge 1: Do this as well as possible and we'll let others vote
as to which version is better.

Challenge 2: Since Bob Allison likes to "walk around" structures, I would
like to see his version of the following (Ugh!) recursive subroutine
that prints a binary tree of integers in infix order (or any other order).
First the necessary declarations, then the subroutine.

   TYPE NODE
      INTEGER :: VALUE
      TYPE (NODE), POINTER :: LEFT, RIGHT
   END TYPE NODE

   RECURSIVE SUBROUTINE PRINT_TREE (T)
   ! Print tree in infix order

      TYPE (NODE), POINTER, INTENT (IN) :: T

      IF (ASSOCIATED (T)) THEN
         CALL PRINT_TREE (T % LEFT)
         PRINT *, T % VALUE
         CALL PRINT_TREE (T % RIGHT)
      END IF

   END SUBROUTINE PRINT_TREE

Jeanne Martin of LLNL, I believe, posted Fortran 8x versions of
Leonard's matrix example and it had none of the properties Bill claimed
it would have to have (I believe).  Maybe she would be willing to
post her example again.

Walt Brainerd   Unicomp, Inc.  brainerd@unmvax.unm.edu

hallidayd@yvax.byu.edu (06/20/89)

By the way Walt, even your Fortran 8x example needs only one pointer (for the
walk) since (according to your own code, message <158@unmvax.unm.edu>) Fortran
8x allows references of the form

      TRAIL_PTR % NEXT % NEXT => TMP_PTR

thus your code for "walking" through the list may be implemented as

   SUBROUTINE INSERT (PTR, NUMBER)
      ! Single pointer version

      TYPE (NODE), POINTER, INTENT (IN) :: PTR
      TYPE (NODE), POINTER :: TRAIL_PTR, TMP_PTR
      INTEGER, INTENT (IN) :: NUMBER

      ! "Walk" through the list to
      ! determine where NUMBER goes
      TRAIL_PTR => PTR
      DO
         IF (.NOT. ASSOCIATED (TRAIL_PTR % NEXT)) EXIT
         IF (NUMBER <= TRAIL_PTR % NEXT % VALUE) EXIT
         TRAIL_PTR => TRAIL_PTR % NEXT      ! Please excuse me if this should
                                            ! actually use the = assignment
                                            ! operator.  (I have not read the
                                            ! latest proposed standard yet.)
      END DO

      ! Insert into sublist
      ALLOCATE (TMP_PTR)
      TMP_PTR % VALUE = NUMBER
      TMP_PTR % NEXT => TRAIL_PTR % NEXT
      TRAIL_PTR % NEXT => TMP_PTR

   END SUBROUTINE INSERT

Actually, if I understand the ``Aliasing'' mode for Fortran 8x pointers,
Fortran 8x pointers are a lot closer to the concept of true recursive data
structures than they are to C style ``addresses''.  Thus the construct

         TRAIL_PTR = TMP_PTR

used in Walt's code will accomplish the wrong thing, it will reassign the value
of the list node ``pointed to''(aliased) by TRAIL_PTR the value of the next
node (the node aliased by TMP_PTR).  This will, in effect, delete the original
node aliased by TRAIL_PTR and leave a duplicate node, aliased by TMP_PTR,
``dangling'' after the execution of the next statement
(  TMP_PTR => TRAIL_PTR % NEXT  ).
This is an example of how most any form of pointer implementation can allow the
programmer to produce erroneous code.  (Unless the standard declares that there
is NO garbage collection, that code which leaves allocated memory unreferenced
is in error, and, further, that constructs which cause such unreferenced
allocated memory will be flagged as erroneous by the compiler.  However, as has
been pointed out by people in the comp.lang.ada news group, there are cases
where data structures may be referenced though several different paths and where
the program (and thus, all the more so, the compiler) may have no idea whether a
given abject has become unreferenced, therefore some form of garbage collection
becomes needed---perhaps being turned on or off by compiler directives.)

Furthermore, Walt, were you not trying to insert _before_ the node that had a
VALUE greater than or equal to the given NUMBER?  This is not what your
recursive routine _appears_ to do.  Instead, it creates a ``dangling'' node,
containing the inserted number, pointing to the node _after_ the one with
the VALUE greater than or less than the NUMBER.  What I expect you wanted
was:

   RECURSIVE SUBROUTINE INSERT (L, NUMBER)

      TYPE (NODE), POINTER, INTENT(IN OUT) :: L
      TYPE (NODE), POINTER :: TMP_L
      INTEGER, INTENT (IN) :: NUMBER

      ! If NUMBER goes here, insert it in new node
      IF (NUMBER <= L % VALUE) THEN
         ALLOCATE (TMP_L)
         TMP_L % VALUE = NUMBER
         TMP_L % NEXT => L   ! Modified
         L => TMP_L          ! lines
      ! Otherwise, insert into sublist
      ELSE
         CALL INSERT (L % NEXT, NUMBER)
      END IF

   END SUBROUTINE INSERT

(Just in the interest of accuracy---I hope! ;-)

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

hankd@pur-ee.UUCP (Hank Dietz) (06/22/89)

In article <638hallidayd@yvax.byu.edu> hallidayd@yvax.byu.edu writes:
...
>      TYPE (NODE), POINTER, INTENT (IN) :: PTR
>      TYPE (NODE), POINTER :: TRAIL_PTR, TMP_PTR
...
>      TRAIL_PTR => PTR
>      DO
>         IF (.NOT. ASSOCIATED (TRAIL_PTR % NEXT)) EXIT
>         IF (NUMBER <= TRAIL_PTR % NEXT % VALUE) EXIT
>         TRAIL_PTR => TRAIL_PTR % NEXT      ! Please excuse me if this should
...

THIS is Fortran code?  Well, at least the names are all uppercase. ;-)

						-hankd@ee.ecn.purdue.edu

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

In article <638hallidayd@yvax.byu.edu>, hallidayd@yvax.byu.edu writes:
> By the way Walt, even your Fortran 8x example needs only one pointer (for the
> walk) 
> 
You are right, but two are needed for the insertion, anyway.

I warned you that there probably would be bugs in the examples.
Of course, I put in a couple just to see if anyone is paying attention!

> Thus the construct
> 
>          TRAIL_PTR = TMP_PTR
> 
> used in Walt's code will accomplish the wrong thing, ...

It sure does do the wrong thing:  = should be =>, of course.

The following lines do indeed fix another error.  Just fell asleep
while either coding or typing, I guess!

>          TMP_L % NEXT => L   ! Modified
>          L => TMP_L          ! lines

Has anyone seen Bob ("walk thru") Allison's nonrecursive version
of my tree printing routine, yet?

Walt Brainerd  Unicomp, Inc.  brainerd@unmvax.cs.unm.edu

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

In article <12018@pur-ee.UUCP>, hankd@pur-ee.UUCP (Hank Dietz) writes:
> In article <638hallidayd@yvax.byu.edu> hallidayd@yvax.byu.edu writes:
> ...
> >      TYPE (NODE), POINTER, INTENT (IN) :: PTR
> >      TYPE (NODE), POINTER :: TRAIL_PTR, TMP_PTR
> ...
> >      TRAIL_PTR => PTR
> >      DO
> >         IF (.NOT. ASSOCIATED (TRAIL_PTR % NEXT)) EXIT
> >         IF (NUMBER <= TRAIL_PTR % NEXT % VALUE) EXIT
> >         TRAIL_PTR => TRAIL_PTR % NEXT      ! Please excuse me if this should
> ...
> 
> THIS is Fortran code?  Well, at least the names are all uppercase. ;-)
> 
I guess I should have headed off this inevitable comment in the first place.
Current Fortran does not have recursion, pointers, or data structures.
That's about all there is in these examples, and it is true, they don't
look much like (current) Fortran.  How could they?  You just can't do
this kind of thing very easily in current Fortran.  Someone
was just saying that IF..ELSE IF..ELSE..END IF doesn't look much like
Fortran (66), but I think most of us are used to it now.
(And, of course, the example could have been done in lowercase!)

An important thing to keep in mind is that the following is (to many people)
the most important addition to Fortran 8x and it sure looks a lot like
Fortran (any version):

      A = B + 2 * C

The catch is that A, B, and C are 100 x 100 arrays.
This is really FORmula TRANSlation, extended to additional kinds
of mathematical objects.

As an aside, though many people treat array processing as the most important
addition now, I think that in 10 years, people will look back and say
that the addition of modules and derived types was at least, if not more,
important (but we need to parameterize the derived types to be useful--
this was removed as a "simplification").

Walt Brainerd   Unicomp, Inc.  brainerd@unmvax.cs.unm.edu

chris@mimsy.UUCP (Chris Torek) (06/23/89)

[I deleted a `distribution: usa'.]

In article <158@unmvax.unm.edu> brainerd@unmvax.unm.edu (Walt Brainerd) writes:
>First, note that there is no need for pointers pointing to pointers.

(They are, however, sometimes convenient; see example below.  None of this
disputes jlg's point---in another article---that `convenient' and `appropriate'
are not always the same.)

>To show the contrast between the C program Bill wrote, the "walk" around
>version in Fortran 8x and the (Ugh!) elegant version using recursion
>even more, let's not pick the particularaly simple example in Bill's
>list insertion, but instead assume the list is to be maintained in
>ascending order.  If, for example, we are to insert the number 17,
>it must work if the list is empty, if all numbers are < 17, or if
>all numbers are > 17.  In this example, you have to make an insertion
>_before_ the node you find having a certain property. To do this,
>I think even nonfreshman need two pointers (a trailing pointer is needed)
>(but maybe someone else can do it with one)
>and the empty list is either a special case (Bill just printed an error mesg)
>or there must always be a dummy node in the list (I have arbitrarily chosen
>the latter).

An empty list need not (and should not, in general) be a special case.

[Code, including bugs corrected in later followups, deleted.  The
insert subroutine itself (that is, without the declarative preamble)
was 16 non-blank non-comment lines.  I counted only what was in the
referenced article, not anything in later corrections.]

For contrast, here is a correct version with a pointer that points
to a pointer, in Classic C.  (Changing it to New C [pANS C] requires
changing the argument list syntax, deleting two lines in the process.)

typedef int data_t;	/* any arithmetic type will do */

struct list {
	data_t	value;
	struct	list *next;
};

struct list *insert(head, newnode)
	struct list *head, *newnode;
{
	register struct list **p = &head;
	register data_t newvalue = newnode->value;

	for (p = &head; *p != NULL && (*p)->value < newvalue; p = &(*p)->next)
		/* void */;
	newnode->next = p;
	*p = newnode;
	return head;
}

The key to the whole thing is the ability to address the local parameter
`head', which is itself a pointer.  In the (empty) body of the `for' loop,
the following condition always holds:

	*p is not nil
		and
	*p points to a node whose value is less than the new value

The loop terminates when one of these conditions is false.  Thus,
either

	*p is nil
		or
	*p points to a node whose value is >= newvalue

(In no case is p itself ever nil.)  At that time, we make the new
node's `next' field be p (nil---the end marker---or something that
should follow).  In either case the list headed by newnode is properly
sorted, provided the input was properly sorted.  We then set *p
to newnode.  If *p was nil, this means that newnode->next is nil,
and that newnode->value must be >= all values in the list headed
by `head'.  If *p was not nil, we have two cases:

	*p aliases head
		or
	*p aliases head->next-> ... ->next

If *p aliases head, the assignment changes head so that newnode heads
the list, which is then properly sorted.  Otherwise, we know (by strong
induction) that the node whose next field is aliased by *p has a value
field which compares less than newnode->value.  The assignment then
replaces this `next' with newnode, and newnode's next is what this
node's next used to be, so again the list is properly sorted.  In
either case, the insert function returns the possibly modified head.

Note that the loop could use `<=' comparisons, and the proof would
still hold (with one change from `>=' to `>'), but if there were
several list elements with the same value, the new node would be
inserted after these elements, rather than before them.
-- 
In-Real-Life: Chris Torek, Univ of MD Comp Sci Dept (+1 301 454 7163)
Domain:	chris@mimsy.umd.edu	Path:	uunet!mimsy!chris

hallidayd@yvax.byu.edu (06/24/89)

Walt, is this true?!?!?
(message <168@unmvax.unm.edu>)
>...
>that the addition of modules and derived types was at least, if not more,
>important (but we need to parameterize the derived types to be useful--
>this was removed as a "simplification").
          ^^^^^^^       !?!?!?!?!?!?!?
>
>Walt Brainerd   Unicomp, Inc.  brainerd@unmvax.cs.unm.edu

Sounds real **BAD** to me!!

Yes I am very glad to be getting array processing, however, I definitely
do agree that the addition of modules and derived types are probably even
more important (in fact, array processing can probably be thought of as a
special case of derived type operator definition and handling).

(FLAME ON --- sorry, I don't usually do this, but...)
(NOT directed at Walt Brainerd --- he seems quite sensible)

As I pointed out to the committee last summer, we need Fortran to be
_innovative_, not just slightly improved (or young physicist, like myself,
will go elsewhere).  Do they _really_ want Fortran to remain ``FORtrash''
in our vernacular?

(FLAME OFF)

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

corbett@beatnix.UUCP (Bob Corbett) (06/24/89)

In article <12018@pur-ee.UUCP> hankd@pur-ee.UUCP (Hank Dietz) writes:
>
>THIS is Fortran code?  Well, at least the names are all uppercase. ;-)
>
>						-hankd@ee.ecn.purdue.edu

     It is not Fortran code yet.  Whether you think it should or should not
be, you will soon have a chance to let your opinion be known.  The second
public review is about to begin.  I urge those who wish to take part in the
review to get a copy of the draft as soon as it is available.  It took me
2 1/2 months of hard reading to understand the previous public review copy
well enough to comment intelligently on it.  I have heard that the next public
review probably will last only two months.  Remember, comments received
after the deadline have no official status.  Be sure to mail your comments
at least a week before the deadline.

						Yours very truly,
						Bob Corbett
						uunet!elxsi!corbett
                                                ucbvax!sun!elxsi!corbett

chris@mimsy.UUCP (Chris Torek) (06/24/89)

In article <18236@mimsy.UUCP> I wrote:
>... here is a correct version ...
>	newnode->next = p;

Aaack!  That should have been `newnode->next = *p'.

>... we make the new node's `next' field be p (nil---the end marker---or ...

Again, *p.  (And I had just noted that p itself is never nil!)  (Actually,
I had added the original parenthetical notes later, and propagated a typo
when I typed the last quoted line above.  Oh well.)
-- 
In-Real-Life: Chris Torek, Univ of MD Comp Sci Dept (+1 301 454 7163)
Domain:	chris@mimsy.umd.edu	Path:	uunet!mimsy!chris

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

In article <646hallidayd@yvax.byu.edu>, hallidayd@yvax.byu.edu writes:
> Walt, is this true?!?!?
> (message <168@unmvax.unm.edu>)
> >...
> >that the addition of modules and derived types was at least, if not more,
> >important (but we need to parameterize the derived types to be useful--
> >this was removed as a "simplification").
>           ^^^^^^^       !?!?!?!?!?!?!?
> >
> >Walt Brainerd   Unicomp, Inc.  brainerd@unmvax.cs.unm.edu
> 
> Sounds real **BAD** to me!!
> 
I am afraid it is true and it IS real BAD.

For example, if you define a new data type "MATRIX" to do the
obvious things with the obvious matrix arithmetic operations,
there is no way to allow the programmer to declare both a 10x10
matrix and a 100x100 matrix using the; same type.  Shades of old Pascal.
It might also be nice to have the "kind" (single or double precision)
be a parameter of the MATRIX data type.

I hope you will comment during the public review!
> 
> (FLAME ON --- sorry, I don't usually do this, but...)
> (NOT directed at Walt Brainerd --- he seems quite sensible)
> 
> As I pointed out to the committee last summer, we need Fortran to be
> _innovative_, not just slightly improved (or young physicist, like myself,
> will go elsewhere).  Do they _really_ want Fortran to remain ``FORtrash''
> in our vernacular?
> 
> (FLAME OFF)
> 
I can't consider this a flame at me as I think I have supported this
philosophy for the last 12 years, but X3J3 has become more and more
reactionary in recent years.  I am not as sure of the "sensible" bit.

Walt Brainerd  Unicomp, Inc.  brainerd@unmvax.cs.unm.edu

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

In article <2766@elxsi.UUCP>, corbett@beatnix.UUCP (Bob Corbett) writes:
> . . . I have heard that the next public
> review probably will last only two months. . . .

Just this week X3 voted to hold a four (4) month review (though the
usual procedure is that the second one is 2 months).  I am sure
someone will post the beginning dates and how to get a copy.  Yes
it does take a bit of time to understand what is there (be glad to come
tell you all about it).  Let's hope the copies from Global Engineering
(the distributor of the document last time) are legible and arrive
in a reasonable time (for the price, you should expect it).

There have been attempts to publish the draft by ACM, but ANSI says
that can't be done because they would not get their royalty from it!
Seems reasonable to make money selling standards, but not drafts.
If you agree, this is something else to comment on.

bobal@microsoft.UUCP (Bob Allison) (06/26/89)

In article <2766@elxsi.UUCP> uunet!elxsi!corbett (Bob Corbett) writes:
>     It is not Fortran code yet.  Whether you think it should or should not
>be, you will soon have a chance to let your opinion be known.  The second
>public review is about to begin.  I urge those who wish to take part in the
>review to get a copy of the draft as soon as it is available.  It took me
>2 1/2 months of hard reading to understand the previous public review copy
>well enough to comment intelligently on it.  I have heard that the next public
>review probably will last only two months.  Remember, comments received
>after the deadline have no official status.  Be sure to mail your comments
>at least a week before the deadline.
>
>						Yours very truly,
>						Bob Corbett
>						uunet!elxsi!corbett
>                                                ucbvax!sun!elxsi!corbett

Well, since I was the one who spread the rumor about the two-month
public review, I should state that in the X3 meeting last week, one of
the issues they discussed and decided on was to have the second Fortran 8x
public review be four months long.  It is now going into the pipe and when
official dates are announced I am sure they will be published in this group.

As an aside to Walt, I still haven't bothered to reply to your comments
about the pointer examples yet because I haven't had the time to sit down
and formulate a good example to demonstrate what I meant by "walking around"
pointers.  The only example I came up with off the top of my head was moderately
artificial and involved using the address of the pointer to indicate when
I have gone full circle in a circular linked list.  Hopefully I will get 
enough free time this week to come up with an example which demonstrates why
I think the 8X pointer proposal will end up falling short for non-trivial
examples.  But keep up the ad hominem attacks: if nothing else, it keeps
my name in print.

Bob Allison

hallidayd@yvax.byu.edu (06/27/89)

Where do we mail our comments during this public review?  I have a hatfull of
comments.

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

jlg@lanl.gov (Jim Giles) (06/28/89)

From article <6174@microsoft.UUCP>, by bobal@microsoft.UUCP (Bob Allison):
> [...]      The only example I came up with off the top of my head was moderately
> artificial and involved using the address of the pointer to indicate when
> I have gone full circle in a circular linked list.  [...]

Bletch!  Well, so much for allowing implementations which occasionally
compact the heap.  If you're counting on the same address (or pointer
value - however they are scaled) to mark the same object each time,
you're probably asking for trouble.  If you need to mark a specific
data object, it is better to _explicitly_ mark it.

hallidayd@yvax.byu.edu (06/28/89)

Chris Torek (chris@mimsy.UUCP), see if the following function is not a
direct port of your C code (message <18236@mimsy.UUCP>, with corrections
given in message <18265@mimsy.UUCP>) to Fortran 8x.

   TYPE (NODE), POINTER FUNCTION  INSERT (HEAD, NEWNODE) ! I believe this to
                                                         ! be proper syntax
                                                         ! for such a FUNCTION

      TYPE (NODE), POINTER :: HEAD, NEWNODE
      TYPE (NODE), POINTER :: PTR
      INTEGER              :: NUMBER = NEWNODE % VALUE   ! I believe the syntax
                                                         ! allows the initial-
                                                         ! ization to involve
                                                         ! the arguments in
                                                         ! this way.
                                                         ! (It should.)

      PTR => HEAD
      DO, WHILE (ASSOCIATED (PTR % NEXT) .AND. PTR % NEXT % VALUE < NUMBER)
                                         ! This (and the C code) work
                                         ! because the .AND. operator
                                         ! is a "short circuit" form.
                                         ! (See Ada for a language that
                                         !  distinguishes between short
                                         !  circuiting and non-short
                                         !  circuiting logical operators.)
         PTR => PTR % NEXT
      END DO
      NEWNODE % NEXT => PTR % NEXT
      PTR % NEXT => NEWNODE
      INSERT = HEAD

   END FUNCTION INSERT

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

hallidayd@yvax.byu.edu (06/28/89)

Referring to Walt Brainerd's (brainerd@unmvax.unm.edu) article (message
<168@unmvax.unm.edu>)

>As an aside, though many people treat array processing as the most important
>addition now, I think that in 10 years, people will look back and say
>that the addition of modules and derived types was at least, if not more,
>important (but we need to parameterize the derived types to be useful--
>this was removed as a "simplification").
                        ^^^^^^^^^^^^^^
>
>Walt Brainerd   Unicomp, Inc.  brainerd@unmvax.cs.unm.edu

I suggest that if the committee really wants to "simplify" Fortran 8x that
they could remove the TYPE(user data type name) construct in favor of
allowing user data types to be used as if they were intrinsic data types in
declaration statements of the form

data_type_name [,attribute[,...]] :: variable_identifier_list

The only need for the TYPE(user data type name) construct is to avoid
ambiguities when using user data types in the _old_ FORTRAN style variable
declaration statements.  Since user data types are _new_, why not restrict
their use to the _new_ form of variable declaration statement where no
possibility for ambiguity may arise?

Another possible "simplification" that seams reasonable (to me) is to
change the POINTER attribute to ALLOCATABLE (after all, the present
proposal uses the ALLOCATE function in much the same way as for ALLOCATABLE
arrays---only the inapplicable subscript range information is missing).
This then (possibly) solves the contention that Fortran POINTERS are "not
really pointers, and will cause confusion for people coming from other
languages with pointers", while giving us the recursive data structures
that are needed.  It also changes ALLOCATABLE arrays from a special class
to being a member of the class of ALLOCATABLE data structures (after all,
arrays are just a special form of data structure).  (It still retains the
ability to reference array sections using the => operator so long as the
referenced array section has the same number of free subscripts as the
ALLOCATABLE array that references it.  We can, rather naturally, limit such
array aliasing to arrays declared with empty subscript ranges (as are used
only for ALLOCATABLE arrays) if we have the ALIAS/IDENTIFY pair, and thus
no need for aliasing arbitrary array sections by other methods.)

Furthermore, if the USE clause is allowed within MODULEs (as it should be,
providing programmers with an inheritance mechanism, which is sorely needed
when the programmer does not have access to the source code) then why do we
need INCLUDE (a poor man's implementation of MODULEs, such as in C)?  Yes,
it can be used to include a set of comments that are common to several
program units, such as copyright notices (though these should, probably, be
actually included in the source files), that will then be displayed in the
compiler listing, but are such uses enough to justify the need for the
INCLUDE?  (Admittedly, INCLUDE is not very expensive for compiler writers
to provide, but it is a "simplification" in the sense that the standard
need not contain the specifications for such a statement).

(The following is grousing over one of the source of the "simplification"
thrust, as I perceive it.)

I don't know if many readers can tell from my postings, but I don't have
much sympathy for the complaints of large companies with widely distributed
FORTRAN compilers that want Fortran 8x to be simply a reflection of their
present compilers (see the Digital Review article that Curtis E Reid
(CEReid@cup.portal.com) commented on in message <19553@cup.portal.com>).
True, we need the input of compiler writers to help us retain connection
with reality, but when their comments are simply complaining about how much
work they will have to do to provide the users with sufficiently powerful
features (which they had not already provided) I take it with a grain of
salt.  A compiler is written once (though maintained over a hopefully long
period of time) while it is used thousands of times by programmers.  Where
should the bulk of the labor reside---the compiler/language, providing
powerful utilities to the programmers using it, or the programmers, having
to work around absent features in the language/compiler?

Personally, I am incensed when a compiler distributer claims they know
exactly what my needs are, and tells me what I do and don't need.  Some of
these companies claim to be providing everything the scientific community
needs (probably justifying this position on the grounds that a large share
of the scientific community uses their compilers and/or hardware).  While
it is true that a great deal of finite difference and finite element code
only needs the array structures of FORTRAN (with some need for dynamically
allocatable arrays so routines need not be rewritten whenever larger arrays
are needed), there are many problems for which old FORTRAN has been
*TOTALLY* inadequate (see for example the article ``Computers in physics:
an overview'' in _Physics Today_, May 1983, Vol. 36 No. 5, by Donald R.
Hamann, pp. 24--33, particularly the subsection ``FORTRAN a curse?'' of the
``Software'' section, pages 29--31).  If the Fortran language proposal is
not "simplified" to death, it may actually win back some of us ``wayward''
scientist for whom Fortran is truly a ``curse''.  (I would use Ada, except
Ada compilers are not widely available, and I hope to make a contribution
to the future of Fortran by standing up for my convictions.)

(Enough grousing from this disgruntled physicist.  Go back to your old
ways, if you wish.)

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

hallidayd@yvax.byu.edu (06/29/89)

Bob Allison (bobal@microsoft.UUCP), here are some responses to your articles
concerning POINTERs (and how you feel the proposed Fortran use of such is not
sufficiently functional):

First, if what you object to is the different definition of ``pointer''
used in the standard---compared to the working definition you have come to
from other languages---then lets simply change the name used in the
proposed Fortran standard (see my posting suggesting we replace POINTER
with ALLOCATABLE, message <662hallidayd@yvax.byu.edu>).  (By the way, if
Bob Corbett (corbett@beatnix.UUCP), or others, can provide the syntactical
and semantic definitions for the fully general recursive data structures
with implicit pointers expressed in message <2775@elxsi.UUCP>, I would
greatly appreciate it.  I don't have any love for ``pointers'', but I do
need recursive data structures.)

Secondly, in response to Walt's desire for an example of ``walking'' through
trees, simply look in _Art of Computer Programming_ by Donald E. Knuth
(walking through using auxiliary stack, pp. 317--318 (of course recursive
calls do this implicitly), or traversal of threaded trees p. 320 ff.), but
I warn you, all the ways expressed in Knuth for traversing trees and other
recursive data structures can be accomplished using Fortran 8x POINTERs.

Thirdly, the only real world application I have seen which requires
POINTERs pointing to POINTERs is the Apple Macintosh's handling of its heap
(to allow the operating system to reconfigure the heap at any time).
However, this use of POINTERs pointing to POINTERs can be handled quite
well, with perhaps even greater clarity than straight forward "pointers
pointing to pointers", using data structures that have only a single field,
with that field being a POINTER (as would be needed using the present
Fortran proposal).  (After all, since the syntax already, automatically,
dereferences the first ``POINTER'' the syntax will look just as if a single
POINTER was being used, with the name of the ``dereferencing'' descripter
(field, operator, whatever) being whatever name seems appropriate to the
programmer.)

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

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

In article <661hallidayd@yvax.byu.edu>, hallidayd@yvax.byu.edu writes:
> Chris Torek (chris@mimsy.UUCP), see if the following function is not a
> direct port of your C code (message <18236@mimsy.UUCP>, with corrections
> given in message <18265@mimsy.UUCP>) to Fortran 8x.
> 
>    TYPE (NODE), POINTER FUNCTION  INSERT (HEAD, NEWNODE) ! I believe this to
                ^^^^^^^^^ Can't put this on function line (irregularity?)
>                                                          ! be proper syntax
>                                                          ! for such a FUNCTION
> 
>       TYPE (NODE), POINTER :: HEAD, NEWNODE
>       TYPE (NODE), POINTER :: PTR
>       INTEGER            :: NUMBER = NEWNODE % VALUE   ! I believe the syntax
                   ^^^^^^^
                   , DATA
                   ^^^^^^^ Until recently, it was proposed that
   you could do this with a DATA attribute; now use the old DATA statement.
>                                                          ! allows the initial-
>                                                          ! ization to involve
>                                                          ! the arguments in
>                                                          ! this way.
>                                                          ! (It should.)
> 
>       PTR => HEAD
>       DO, WHILE (ASSOCIATED (PTR % NEXT) .AND. PTR % NEXT % VALUE < NUMBER)
>                                          ! This (and the C code) work
>                                          ! because the .AND. operator
>                                          ! is a "short circuit" form.
                                             ^^^^^^^^^^^^^^^^^^^^^^^^^
>                                          ! (See Ada for a language that
>                                          !  distinguishes between short
>                                          !  circuiting and non-short
>                                          !  circuiting logical operators.)

Nope!  Fortran says things can be evaluated in any order, so this will
not (necessarily) work if PTR % NEXT is not ASSOCIATED.

>          PTR => PTR % NEXT
>       END DO
>       NEWNODE % NEXT => PTR % NEXT
        . . .

This person obviously has gotten the hang of the new pointers.
Glad to see others giving these things a shot to see how they work.

Walt Brainerd  Unicomp, Inc.  brainerd@unmvax.cs.unm.edu
-- 
Walt Brainerd  Unicomp, Inc.  brainerd@unmvax.cs.unm.edu

hallidayd@yvax.byu.edu (07/04/89)

Walt (brainerd@unmvax.unm.edu, message <194@unmvax.unm.edu>) corrected a
few lines of my Fortran code (message <661hallidayd@yvax.byu.edu>), I thank
you Walt.  However, I have a few comments on the comments (comments
concerning the apparent state of the latest proposed standard).

>>    TYPE (NODE), POINTER FUNCTION  INSERT (HEAD, NEWNODE) ! I believe this to
>                ^^^^^^^^^ Can't put this on function line (irregularity?)
Are we allowed to use (note the double colon)

      TYPE (NODE), POINTER :: FUNCTION ...

If not, then I would indeed say we have an irregularity that should be
corrected (IMHO).  I recognize the need for the double colon to prevent
ambiguity, especially in the future when we may allow such attributes as
FUNCTION or SUBROUTINE, so I have no problem using it here.  (A further
note here concerning ambiguities, when the double colon form of declaration
is used let's allow the user defined type to be used without the
TYPE(user_type_name) construct---in fact, I would not mind if user defined
type names are only allowed to be used in the double colon form of
declaration statement.)

> ...
>>
>>       TYPE (NODE), POINTER :: HEAD, NEWNODE
>>       TYPE (NODE), POINTER :: PTR
>>       INTEGER            :: NUMBER = NEWNODE % VALUE   ! I believe the syntax
>                   ^^^^^^^
>                   , DATA
>                   ^^^^^^^ Until recently, it was proposed that
>   you could do this with a DATA attribute; now use the old DATA statement.
I very much prefer the DATA attribute, rather than the old style DATA
statement.  I would much rather see the old style DATA statement put on the
Obsolescent Feature list than give up the DATA attribute.  (Why are we to
be forced to stick with the old ways of FORTRAN simply because that _was_
the way things were done in the past---let Fortran *evolve*, allow us to
use improved methods and constructs, *PLEASE*.  This is directed as much to
users that complain that _new_ Fortran is not _old_ FORTRAN and therefore
undesirable, as it is directed at the standards committee.  It contains
_old_ FORTRAN as a proper subset, and will for at least a decade to come.
Why is that not enough????)

> ...
>>
>>       PTR => HEAD
>>       DO, WHILE (ASSOCIATED (PTR % NEXT) .AND. PTR % NEXT % VALUE < NUMBER)
>>                                          ! This (and the C code) work
>>                                          ! because the .AND. operator
>>                                          ! is a "short circuit" form.
>                                             ^^^^^^^^^^^^^^^^^^^^^^^^^
>>                                          ! (See Ada for a language that
>>                                          !  distinguishes between short
>>                                          !  circuiting and non-short
>>                                          !  circuiting logical operators.)
>
>Nope!  Fortran says things can be evaluated in any order, so this will
>not (necessarily) work if PTR % NEXT is not ASSOCIATED.
You are absolutely correct.  I forget sometimes because the "short circuit"
form for the .AND. and the .OR. is the way all compilers I have used thus
far have treated these operators.

What we have in FORTRAN is actually something in between the "short
circuit" form, and a complete evaluation of logical statements using
logical `and' and `or' constructs.  I would prefer to be able to choose
between full evaluation and "short circuit" forms on a case by case basis,
as is available in Ada.  This would basically involve the standard
designating another set of logical `and' and `or' operators, and indicating
that either the new `and' and `or' operators are of the "short circuit"
variety and that the old operators are to have all operands evaluated, or,
the reverse, have the old .AND. and .OR. defined to be the "short circuit"
variety.  (Having the old .AND. and .OR. operators defined to have all
operands evaluated would be the closest to the present standard though the
other choice would be the closest to present, though incorrect, practice.)

Maybe, for performance reasons, we should have (yuk?) three types of
logical `and' and `or' operators.  One acting in the way the present .AND.
and .OR. do (retaining their meaning and indeterminacy), another for "short
circuit" forms (greater control over what is and what is not evaluated),
and the third defined to have all operands fully evaluated.  As it is, we
can simulate the full evaluation form of logical statements by evaluating
all function calls prior to the logical statement, and we can simulate the
"short circuit" form by a series of separate conditional statements (which
is probably more difficult to optimize than a true "short circuit" form
would be, and is certainly more messy).

Personally, I could live with the present set of logical operators, defined
in their present, indeterminate, way (for performance reasons), if we are
given the addition of true "short circuit" logical `and' and `or' operators
(recognizing that the control flow nature of the new `and' and `or'
operators would make them unable to be overloaded---no problem).  I don't
remember what the "short circuit" forms are called in Ada (some people
would want to stay away from whatever Ada did, but I feel we can learn a
few things, including what NOT to do, from Ada), but I feel .AND_THEN. (or
.AND_IF.) and .OR_ELSE. may be good names for the "short circuit" form of
logical `and' and `or' operators, since only if the left hand operand to
the .AND_THEN. is true will we also evaluate the right hand operand to
determine the outcome, while if the left hand operand of the .OR_ELSE.
operator is true we do not need to (and will not) evaluate the right hand
operand.  What do others think concerning this?

   _____________________________________
  / David Halliday                      \
  |                                     |
  | Internet:    hallidayd@yvax.byu.edu |     Let Fortran be the BEST it
  | BITNET:      hallidayd@byuvax       |     can be!
  | Us Mail:     BYU Physics Department |
  |              296 ESC                |
  |              Provo, UT  84602       |
  \_____________________________________/

jlg@lanl.gov (Jim Giles) (07/05/89)

From article <673hallidayd@yvax.byu.edu>, by hallidayd@yvax.byu.edu:
> Are we allowed to use (note the double colon)
> 
>       TYPE (NODE), POINTER :: FUNCTION ...

Since FUNCTION is an attribute of the thing being declared and not part
of the thing being declared, the only consistent way to allow double colon
on function declarations would be:

      TYPE (NODE), POINTER, FUNCTION :: ...

By the way, I think the commas in the above ought to be optional.  After
all, in Fortran 77, the following declaration is legal (in fact commas 
_aren't_ allowed):

      INTEGER FUNCTION TEST (A...

With the double colon this becomes:

      INTEGER FUNCTION :: TEST (A...

I think commas should be optional before the double colon in _all_
declarations.

> [...]                                                       (A further
> note here concerning ambiguities, when the double colon form of declaration
> is used let's allow the user defined type to be used without the
> TYPE(user_type_name) construct---in fact, I would not mind if user defined
> type names are only allowed to be used in the double colon form of
> declaration statement.)

I completely agree here.  I would much prefer to see the following
differrences from the proposed syntax:

>>>       TYPE (NODE), POINTER :: HEAD, NEWNODE
      NODE POINTER :: HEAD, NEWNODE
>>>       TYPE (NODE), POINTER :: PTR
      NODE POINTER :: PTR
etc.

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

In article <673hallidayd@yvax.byu.edu>, hallidayd@yvax.byu.edu writes:
> >>    TYPE (NODE), POINTER FUNCTION  INSERT (HEAD, NEWNODE) ! I believe this to
> >                ^^^^^^^^^ Can't put this on function line (irregularity?)
> Are we allowed to use (note the double colon)
No, sorry!  My view is that the presence of the type at all is the irregularity
and that the function value should be declared elsewhere.  There is some
movement to have the RESULT variable be declared, not the function name
when the RESULT is present (required for recursive functions), so that
will push things more in the direction of not having declaration stuff
on the FUNCTION line.
> >>       INTEGER            :: NUMBER = NEWNODE % VALUE   ! I believe the syntax
> >                   ^^^^^^^
> >                   , DATA
> >                   ^^^^^^^ Until recently, it was proposed that
> >   you could do this with a DATA attribute; now use the old DATA statement.
> I very much prefer the DATA attribute, rather than the old style DATA
> statement.  I would much rather see the old style DATA statement put on the
> Obsolescent Feature list than give up the DATA attribute.  (Why are we to
> be forced to stick with the old ways of FORTRAN simply because that _was_
> the way things were done in the past---let Fortran *evolve*, allow us to
> use improved methods and constructs, *PLEASE*.  This is directed as much to
> users that complain that _new_ Fortran is not _old_ FORTRAN and therefore
> undesirable, as it is directed at the standards committee.  It contains
> _old_ FORTRAN as a proper subset, and will for at least a decade to come.
> Why is that not enough????)
> 
Because the collected wisdom of X3J3 thinks so and the "public" seems to
get very upset when things are perceived as changing too much.
(Of course, I agree with you.)

Personally, I think the way you did it without the DATA "attribute"
would be just fine (some don't think DATA is an attribute, just the
keyword of a statement used to provide initial values).

> Personally, I could live with the present set of logical operators, defined
> in their present, indeterminate, way (for performance reasons), if we are
> given the addition of true "short circuit" logical `and' and `or' operators

I think you can always get the "short circuit" effect with nested IF statements
and other (minor??) inconveniences, so I don't believe there would be
too much sympathy for this addition, but asking never hurts.

Thanks for trying out some Fortran 8x features.
These little examples bring out lots of interesting points, I think.
It's real tough to do when a) there is no compiler to check it
(only other people who will find your errors for you!), and
b) the proposed standard keeps changing.

I am off tomorrow to WG5 meeting in Ispra, Italy and X3J3 meeting
in Vienna.  It's nasty work, but somebody must do it!
-- 
Walt Brainerd  Unicomp, Inc.  brainerd@unmvax.cs.unm.edu

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

Jim Giles (jlg@lanl.gov), concerning your desire for optional commas in
declaration statements (message <13971@lanl.gov>):
>From article <673hallidayd@yvax.byu.edu>, by hallidayd@yvax.byu.edu:
>> Are we allowed to use (note the double colon)
>>
>>       TYPE (NODE), POINTER :: FUNCTION ...
>
>Since FUNCTION is an attribute of the thing being declared and not part
>of the thing being declared, the only consistent way to allow double colon
>on function declarations would be:
>
>      TYPE (NODE), POINTER, FUNCTION :: ...
>
Actually, the declaration is giving the TYPE of an entity which is a
FUNCTION.  While this is not much different from declaring an entity that
has the FUNCTION attribute, when (an if), in the future, we are able to
declare, for instance, arrays of functions (something that could be very
helpful in programming multi-program multi-processor type parallel
machines, as opposed to single-program  multi-processor type machines for
which the present Fortran proposal is well suited), the distinction will be
significant.

>By the way, I think the commas in the above ought to be optional.  After
>all, in Fortran 77, the following declaration is legal (in fact commas
>_aren't_ allowed):
>
>      INTEGER FUNCTION TEST (A...
>
>With the double colon this becomes:
>
>      INTEGER FUNCTION :: TEST (A...
>
>I think commas should be optional before the double colon in _all_
>declarations.
>
>> [...]                                                       (A further
>> note here concerning ambiguities, when the double colon form of declaration
>> is used let's allow the user defined type to be used without the
>> TYPE(user_type_name) construct---in fact, I would not mind if user defined
>> type names are only allowed to be used in the double colon form of
>> declaration statement.)
>
>I completely agree here.  I would much prefer to see the following
>differrences from the proposed syntax:
>
>>>>       TYPE (NODE), POINTER :: HEAD, NEWNODE
>      NODE POINTER :: HEAD, NEWNODE
>>>>       TYPE (NODE), POINTER :: PTR
>      NODE POINTER :: PTR
>etc.
You can't have both the ability to use user defined types without the
TYPE(user_type_name) construct, and optional commas, unless we have
significant blanks (so they are not allowed in the middle of identifiers,
like type names, and so the user is required to use the blank as a
separator).  While I have no objection to this, and such a source form is
allowed in the proposed standard, we must maintain compatibility with the
old fixed source form of FORTRAN 77 (and before) which allows blanks to be
invisible.

We could allow commas to be optional and the TYPE(user_type_name) construct
dropped in "free" source form, while requiring commas for the older "fixed"
source form, but this is an added complication that requires the programmer
to use different rules for different source forms.  Another possibility, if
the Fortran 8x standards committee, and we as users, are truly sold on the
idea that the "free" source form is the way of the future (I think some
such form is indeed the way of the future) then we could restrict the more
descriptive declaration statements to only be used in "free" source form,
thus allowing for backward compatibility with _old_ FORTRAN, while moving
to the future with the _new_ Fortran.  (However, the _old_ FORTRAN
community may not be willing to live with such a restriction.)

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

smryan@garth.UUCP (s m ryan) (07/13/89)

>Bletch!  Well, so much for allowing implementations which occasionally
>compact the heap.  If you're counting on the same address (or pointer

Feh! If the cell is moved, all references to that cell must be remapped.
Compaction must be invisible or the collector is broken.
-- 
22. His eldest son was Fafnir sere                Steven Ryan: ingr!garth!smryan
and the other Regin filled with fear.              2400 Geng Road, Palo Alto, CA
They asked a share of Otter's gold
but father chose his treasure cold.              For Grid, Goofy, and St Mickey.

jlg@lanl.gov (Jim Giles) (07/14/89)

From article <3111@garth.UUCP>, by smryan@garth.UUCP (s m ryan):
>>Bletch!  Well, so much for allowing implementations which occasionally
>>compact the heap.  If you're counting on the same address (or pointer
> 
> Feh! If the cell is moved, all references to that cell must be remapped.
> Compaction must be invisible or the collector is broken.

Wait a minute!  How does the memory manager know that you've copied the
value of a pointer into a temporary variable (for circular list detect)?
Unless you want all pointer assignments to be implemented as subroutine
calls to the memory manager, the manager only knows those references
that the block was allocated to.  (It's issues like this that cause me
to oppose introducing pointers in the first place.)