[comp.lang.fortran] Function calls in the middle of subroutine CALLs? -- Is it standard fortran 77 ????

forrest@eemips.tamu.edu (Bob Forrest) (07/06/90)

       I want to dynamically allocate memory in fortran by using
mixed languages (C and FORTRAN).  In so doing, I need to pass
a value contained in a variable to other routines by value instead
of by address --   %VAL(variable_name)   under several vendors extensions to 
Fortran 77; However, not all vendors have an extension to Fortran 77
such as %VAL().  Having a C function call in the middle of a Fortran
subroutine call works on some vendors platforms.  My question is:
"Is it part of the FORTRAN 77 standard to be allowed to make function
calls in the middle of a subroutine CALL?  -- assuming only FORTRAN
(I expect mixed language programming such as FORTRAN and C is not
part of the fortran 77 standard...)".  If anyone knows the answer
to whether function calls are allowed in the middle of subroutine
calls, I would appreciate them letting me know it.

    Thanks.


bob forrest
forrest@ee.tamu.edu   -- internet
forrest@tamvxee       -- bitnet

       INTEGER BITMAP,IPSVAL,IER,ISIZE,GETVM,IXDIM,IYDIM
       REAL XLOC,YLOC
       EXTERNAL GETVM,IPSVAL
C        other fortran code and ISIZE calculation...
C        assume for example that we end up having
       IXDIM = 50
       IYDIM = 50
       ISIZE = IXDIM*IYDIM
C        now we call a C routine to allocate the space...
       IER = GETVM(BITMAP,ISIZE)
C         the variable BITMAP now contains the address of the beginning
C         of the dynamically allocated memory.
C        ...other fortran code...
C        now the function call IPSVAL() in the middle of the 
C       putdot subroutine call...????
       CALL PUTDOT(XLOC,YLOC,IPSVAL(BITMAP),IXDIM,IYDIM)
C        ... more fortran code...
       

worley@compass.com (Dale Worley) (07/09/90)

forrest@eemips.tamu.edu (Bob Forrest) writes:
>        I want to dynamically allocate memory in fortran by using
> mixed languages (C and FORTRAN).  In so doing, I need to pass
> a value contained in a variable to other routines by value instead
> of by address --   %VAL(variable_name)   under several vendors extensions to 
> Fortran 77;

A more portable solution is to pass the variable by address (that is,
call the C routine in the ordinary Fortran way), but have the C
routine fetch the value from its location.  This leaves your Fortran
completely portable and your C only somewhat less so -- fetching a
value from an address is C is easy.

> "Is it part of the FORTRAN 77 standard to be allowed to make function
> calls in the middle of a subroutine CALL?

Yes.  Unless Fortran 77 is crazy...

Dale Worley		Compass, Inc.			worley@compass.com
--
The United States has entered an anti-intellectual phase in its
history, perhaps most clearly seen in our virtually thought-free
political life. -- David Baltimore

burley@world.std.com (James C Burley) (07/15/90)

In article <6381@helios.TAMU.EDU> forrest@eemips.tamu.edu (Bob Forrest) writes:

   "Is it part of the FORTRAN 77 standard to be allowed to make function
   calls in the middle of a subroutine CALL?  -- assuming only FORTRAN
   (I expect mixed language programming such as FORTRAN and C is not
   part of the fortran 77 standard...)"....
       Thanks.
   bob forrest
   forrest@ee.tamu.edu   -- internet
   forrest@tamvxee       -- bitnet

	  CALL PUTDOT(XLOC,YLOC,IPSVAL(BITMAP),IXDIM,IYDIM)

Yes (and no).  You can do what is shown in the example you provide, as long
as you understand that the function call is not made "in the middle" of the
subroutine call, but prior to that call (and the result passed to the
subroutine as an argument).  But it seems clear you mean "in the middle" only
in the sense of "as one of the arguments for a subroutine call".

dmurdoch@watstat.uwaterloo.ca (Duncan Murdoch) (07/19/90)

In article <BURLEY.90Jul14154236@world.std.com> burley@world.std.com (James C Burley) writes:
>In article <6381@helios.TAMU.EDU> forrest@eemips.tamu.edu (Bob Forrest) writes:
>
>   "Is it part of the FORTRAN 77 standard to be allowed to make function
>   calls in the middle of a subroutine CALL?  -- assuming only FORTRAN
>
>Yes (and no).
...
>But it seems clear you mean "in the middle" only
>in the sense of "as one of the arguments for a subroutine call".

Does the standard specify in what order the arguments will be evaluated?
If they have side effects, it makes a big difference sometimes. I've been
bitten by a bug caused by the lack of such specification in Pascal.

Duncan Murdoch

burley@world.std.com (James C Burley) (07/19/90)

In article <1990Jul19.014856.13421@maytag.waterloo.edu> dmurdoch@watstat.uwaterloo.ca (Duncan Murdoch) writes:

   Does the standard specify in what order the arguments will be evaluated?
   If they have side effects, it makes a big difference sometimes. I've been
   bitten by a bug caused by the lack of such specification in Pascal.

The standard says arguments may be evaluated in any order by any implementation
at any time -- a given implementation (compiler) is not even required to
evaluate function refs in a procedure call the same way each time it compiles
it or consistently among identical calls.

The reasoning behind not specifying an order for these sorts of things is
twofold (at least): one, there isn't a visual ordering in the procedure call
(not everyone reads left to right naturally) and side effects in function
calls are not naturally obvious, so writing code that used any ordering would
result in harder-to-read code; two, it allows a compiler to perform
optimizations that might not be obtainable given a mandated ordering
(especially on machine with parallel computational units).

If you need to do something like "CALL X(F(1),G(2))" and you care about the
ordering, you should do the following instead:

    TEMP1 = F(1)
    TEMP2 = G(2)  !Or the opposite order if you desire
    CALL X(TEMP1,TEMP2)

That way the ordering is imposed on the optimizer only when necessary (as
in this case) and is immediately obvious to anyone reading the code, without
the need for further comments (it even suggests F and G might have side-effects
though comments should still be used to clarify this, just in case someone
says "aha! I'll make the code prettier by doing away with the temps!").

jlg@lanl.gov (Jim Giles) (07/19/90)

In article <1990Jul19.014856.13421@maytag.waterloo.edu> dmurdoch@watstat.uwaterloo.ca (Duncan Murdoch) writes:
> [...]
>    Does the standard specify in what order the arguments will be evaluated?
>    If they have side effects, it makes a big difference sometimes. I've been
>    bitten by a bug caused by the lack of such specification in Pascal.
> [...]

The Fortran standard allows functions to have side effects.  But, it does
_not_ allow such functions to be called in the same statement with other
objects that might be effected by those side effects.  For example:

      x = f(a) + g(x)

Now, if g modifies x, the above statement is illegal.  Similarly, if
x is in common, f may modify x and also cause the statement to be illegal.
Finally, f and g may share data through common which causes a difference
in their evaluation - this would also be illegal.  The rule is actually
very simple:

      In a statement that contains more than one function reference,
      the value provided by each function reference must be independent
      of the order chosen by the processor for evaluation of the
      function references.  [ANSI X3.9-1978, section 6.6.2]

The standard also permits common expression elimination, ie. the
evaluation of a common subexpression once with the result being used
repeatedly.  This led to such things as follows:

      x = f(a) + f(a)
becomes
      x = 2 * f(a)

This had some rather sad consequences for naive users trying to get two
samples from a random number generator in the same expression.  The
way around this problem for random number generators was to use:

      x = rnd(0) + rnd(1)

The optimizer didn't recognize the two calls as common expressions,
so it didn't optimize them.  The rnd() function was written to ignore
its argument though - so the result here is the sum of two successive
random variates.  Note: you _still_ can't count on which _order_ the
two calls are made in.

J. Giles

seymour@milton.u.washington.edu (Richard Seymour) (07/20/90)

In article <1990Jul19.014856.13421@maytag.waterloo.edu> dmurdoch@watstat.uwaterloo.ca (Duncan Murdoch) writes:
>In article <BURLEY.90Jul14154236@world.std.com> burley@world.std.com (James C Burley) writes:
>>In article <6381@helios.TAMU.EDU> forrest@eemips.tamu.edu (Bob Forrest) writes:
>>   "Is it part of the FORTRAN 77 standard to be allowed to make function
>>   calls in the middle of a subroutine CALL?  -- assuming only FORTRAN
>>But it seems clear you mean "in the middle" only
>>in the sense of "as one of the arguments for a subroutine call".
>
>Does the standard specify in what order the arguments will be evaluated?
>If they have side effects, it makes a big difference sometimes. I've been
>bitten by a bug caused by the lack of such specification in Pascal.

the old fortran 66 convention used to be left-to-right (unless overridden
 by operator precedence).  but they were talking expression evaluation.
DEC VMS F77 compiler very definitely warns you that optimization
can really mess up the left-to-right stuff.  Even providing guiding
parentheses gets overridden by the optimizer.  Even turning off
optimization (in various releases of the compiler) did not protect
you (or me (can you say "bitten"? shure you can...)) from occasional
non left-to-right reordering of an expression.
separating the critical steps to separate statement lines AND
turning off optimization DID control non-obvious flow
(i had variables in COMMON which were being asynchronously diddled,
or actual device registers appearing as variables).
SO -- the only way i've found to really be sure of execution order
is to read the machine-language listing of the compiled program.
The slightly less-ssure way is to expicitly pre-resolve function calls,
etc. in previous lines, then call subroutines with only variable names
in the argument list.
Proper Structure Procedure (something i'm NEVER accused of) would dictate
that any function/subroutine should  ONLY affect items in the argument
list (a function returns only the one value that it's called, right?),
not background hidden things in COMMON, etc.
Following that programming convention also guarantees not being bitten.
good luck
--dick

buckland@cheddar.ucs.ubc.ca (Tony Buckland) (07/20/90)

In article <5283@milton.u.washington.edu> seymour@milton.u.washington.edu (Richard Seymour) writes:
 
>the old fortran 66 convention used to be left-to-right (unless overridden
> by operator precedence).  but they were talking expression evaluation.
>DEC VMS F77 compiler very definitely warns you that optimization
>can really mess up the left-to-right stuff.  Even providing guiding
>parentheses gets overridden by the optimizer.
 
 A pity.  Many years ago when FORTRAN meant FORTRAN-IV, I wrote
 a package of functions to perform pieces of a task (string 
 decomposition and manipulation, if you must know) as functions
 just so that I could achieve the compactness of
 
    R = ONE(A,B)+TWO(A,B,C)+THREE(A,C)+FOUR(A)
 
 Where R is a more-or-less useless result and the statement
 really means "do thing 1 to arguments A and B, then do thing
 2 to A, B and C, then ..." where A, B, C were modified by the
 operations and order mattered very much.  Nevermore; sigh.

burley@world.std.com (James C Burley) (07/20/90)

Also, I think the standard allows an implementation to take a statement
like

    X = Y * FN(Z)

and, if Y is 0.0 at compile time or even at run time, skip the call to FN(Z)
(which might have side effects) and just produce a result of 0.0.  If FN might
define Z in the call, then Z is considered undefined after such a statement
(even if the compiler you're using does no such optimization) because it
MIGHT have not actually gotten defined; you can't even expect Z to have
"either the old or new value, depending on whether F(Z) ever got called", if
you're writing a standard-conforming program.

I guess the real issue is that Fortran is a language primarily for the
expression of mathematical formulas, in which side effects and operation
ordering do not play a role.  When you care about side effects and ordering,
you are told to use separate statements (or other sequence points like
IF (condition) statement, where condition is guaranteed to be tested before
statement gets executed).  Only computational vs. mathematical issues are
introduced in Fortran expressions, so A*(B*C) is not computationally the same
as (A*B)*C even though they are mathematically the same; but that is necessary
because Fortran is a computational-model math blaster.

hirchert@ux1.cso.uiuc.edu (Kurt Hirchert) (07/20/90)

1. On the subject of functions with side effects:

   a. Fortran allows functions with side effects.
   b. However, you are not allowed to use a function with a side effect if that
      side effect could change the value of any other expression or
      subexpression in the same statement.  (The one exception to this general
      rule is that in a statement of the form IF(<expression>)<statement>,
      a side-effect in <expression> _can_ affect <statement>.
   c. Fortran does not guarantee that your function with side-effects will be
      executed.  If the expression in which it appears can be evaluated without
      it, your processor is free to skip the execution of the function.  If
      there is a possibility of this occurring, whether or not your processor
      suppresses the execution of the function, the standard calls for you
      to consider the side-effects of the function to be undefined and
      prohibits your making use of them.  (Since the standard does not limit
      the methods the processor can use in determining the expression value
      without calling the function, it has been argued that you should always
      treat function side-effects as undefined.)
   d. All of the above contributes to my recommendation that you not use
      functions with side-effects in Fortran.  The programming style where
      everything is done by functions that return status codes may be a good
      style for programming in C, but in Fortran it is likely to give you
      problems, especially if you are trying to write portable code.  (This
      is why the intrinsic random number generator and date and time inquiries
      in Fortran 90 were made subroutines rather than functions.)

2. On the subject of the order of evaluation:

   a. A left-to-right rule is used to determine the mathematical meaning of an
      expression.  (A right-to-left rule is used for the ** operator.)  Thus,
      A-B-C means (A-B)-C, not A-(B-C).
   b. In the absence of parentheses, processor is free to make mathematically
      equivalent transformations in performing the evaluation of the
      expression, even though the "equivalent" expressions may not produce the
      same result in machine arithmetic.  For example, A-B-C may be evaluated
      as (A-B)-C, A-(B+C), (A-C)-B, -(B-(A-C), (-C+A)-B, etc.
   c. However, a processor must not violate parentheses.  If your processor
      evaluates (A*B)*C as A*(B*C), it is broken!  (Unless, of course, it can
      prove that this produces exactly the same machine result.)  Ditto,
      evaluating A*(B+C) as A*B+A*C.

The above rules apply equally to FORTRAN 66, FORTRAN 77, and Fortran 90,
although the implications of the rules may not be evident on particular
implementations of these standards (e.g., FORTRAN IV).
-- 
Kurt W. Hirchert     hirchert@ncsa.uiuc.edu
National Center for Supercomputing Applications

mayne@VSSERV.SCRI.FSU.EDU (William (Bill) Mayne) (07/20/90)

In article <BURLEY.90Jul19220745@world.std.com> burley@world.std.com (James C Burley) writes:
>
>I guess the real issue is that Fortran is a language primarily for the
>expression of mathematical formulas, in which side effects and operation
>ordering do not play a role.  When you care about side effects and ordering,
>you are told to use separate statements (or other sequence points...
>
Correct me if I am wrong (I am new to high performance computing), but
isn't there risk that an optimizing compiler will rearrange even separate
statements in some cases. Relying on side effects seems quite dangerous.
Your explanation was so good I'd like to hear more. Regards.

saltzman@mora.rice.edu (Matthew Saltzman) (07/21/90)

In article <1990Jul20.153135.11273@ux1.cso.uiuc.edu> hirchert@ux1.cso.uiuc.edu (Kurt Hirchert) writes:
>1. On the subject of functions with side effects:
>
>   a. Fortran allows functions with side effects.
>   b. However, you are not allowed to use a function with a side effect if that
>      side effect could change the value of any other expression or
>      subexpression in the same statement.  (The one exception to this general
>      rule is that in a statement of the form IF(<expression>)<statement>,
>      a side-effect in <expression> _can_ affect <statement>.
(A couple of other postings have asserted something similar.) 

I'm sorry, but I don't see how a compiler can practically enforce such a 
restriction.  *Any* time a variable appears as an argument to a function,
it's a candidate for modification.  If I write
	X = F(Y) + Y + Z
how can the compiler know if Y is modified by F()?  F() doesn't need to
even appear in the same source file as the statement.  Detection of the
modification at run-time seems to be an unreasonable restriction on
optimization.   F() could even modify Z, if Z appeared in COMMON.
Am I missing something?

>   c. Fortran does not guarantee that your function with side-effects will be
>      executed.  If the expression in which it appears can be evaluated without
>      it, your processor is free to skip the execution of the function.  If
>      there is a possibility of this occurring, whether or not your processor
>      suppresses the execution of the function, the standard calls for you
>      to consider the side-effects of the function to be undefined and
>      prohibits your making use of them.  (Since the standard does not limit
>      the methods the processor can use in determining the expression value
>      without calling the function, it has been argued that you should always
>      treat function side-effects as undefined.)

This is a reasonable specification, but it is not the same as "not allowed."
My Sun FORTRAN compiler has no problem with the above construct (with
F(Y) modifying Y).  I understand that if I actually *did* do this, it 
would be at my peril.

>   d. All of the above contributes to my recommendation that you not use
>      functions with side-effects in Fortran.

Yes!

> [deleted]
>Kurt W. Hirchert     hirchert@ncsa.uiuc.edu
>National Center for Supercomputing Applications

	Matthew Saltzman
	saltzman@rice.edu

Disclaimer: Institutions can't have opinions.

jlg@lanl.gov (Jim Giles) (07/21/90)

From article <10074@brazos.Rice.edu>, by saltzman@mora.rice.edu (Matthew Saltzman):
>> [...]
>>   b. However, you are not allowed to use a function with a side effect if that
>>      side effect could change the value of any other expression or
>>      subexpression in the same statement.  [...]
> [...]
> I'm sorry, but I don't see how a compiler can practically enforce such a 
> restriction.  *Any* time a variable appears as an argument to a function,
> it's a candidate for modification.  [...]

Who said anything about "compiler", "practically", or (more specifically)
"enforce"?  The Fortran standard describes a language - _not_ a compiler.
The standard only prescribes the behaviour of compliant programs. A
compiler which produces the described behaviour for all compliant
programs is a compliant implementation - regardless of what it does
with (to) non-compliant programs.

What the above rule really means is that a compliant implementation
may _assume_ that compliant programs obey the rule - and can optimize
accordingly.  The only programs that suffer from this are those which
don't comply with the standard anyway - and the standard says _nothing_
about how _those_ should behave.  ANSI C is strewn with similar stuff -
including the unpredictability of the order of side-effects in function
calls.  I suspect it is a common feature of all formally specified
procedural languages - otherwise the language wouldn't compete well
with those that _do_ permit such optimizations.

J. Giles

burley@world.std.com (James C Burley) (07/21/90)

In article <8768@ubc-cs.UUCP> buckland@cheddar.ucs.ubc.ca (Tony Buckland) writes:

    A pity.  Many years ago when FORTRAN meant FORTRAN-IV, I wrote
    a package of functions to perform pieces of a task (string 
    decomposition and manipulation, if you must know) as functions
    just so that I could achieve the compactness of

       R = ONE(A,B)+TWO(A,B,C)+THREE(A,C)+FOUR(A)

    Where R is a more-or-less useless result and the statement
    really means "do thing 1 to arguments A and B, then do thing
    2 to A, B and C, then ..." where A, B, C were modified by the
    operations and order mattered very much.  Nevermore; sigh.

It is nice to be able to express things like this compactly, but this isn't
what Fortran has ever been intended to provide, especially because it looks
(and is) rather difficult to maintain, since technically ONE through FOUR
must be written as functions when they would appear (to somebody just looking
at them) to operate usefully only as subroutines.

For this kind of compactness, C has the comma operator to indicate both
ordering of operations (left to right) and return the final expression.
Sure it's useful in some cases, but not for the kind of programming Fortran
people usually want to do.  And since C has free-form syntax and no CALL
keyword, "r = one(a), two(b), three(c), four(d);" is actually less compact
and readable than the (equivalent if you discard "r") statements
"one(a); two(b); three(c); four(d);".

In Fortran 90, you could at least write:

    CALL ONE(A); CALL TWO(B); CALL THREE(C); CALL FOUR(D)

This is nice because it is a lot more readable, and subroutines are really
subroutines, men are really men, and small furry creatures from alpha
centauri ... oh, never mind!

burley@world.std.com (James C Burley) (07/21/90)

In article <286@sun13.scri.fsu.edu> mayne@VSSERV.SCRI.FSU.EDU (William (Bill) Mayne) writes:

   In article <BURLEY.90Jul19220745@world.std.com> burley@world.std.com (James C Burley) writes:
   >
   >I guess the real issue is that Fortran is a language primarily for the
   >expression of mathematical formulas, in which side effects and operation
   >ordering do not play a role.  When you care about side effects and ordering,
   >you are told to use separate statements (or other sequence points...
   >
   Correct me if I am wrong (I am new to high performance computing), but
   isn't there risk that an optimizing compiler will rearrange even separate
   statements in some cases. Relying on side effects seems quite dangerous.
   Your explanation was so good I'd like to hear more. Regards.

I used to work on just such an optimizer for a vector processor, and you're
right, there is such a risk: but technically the risk is that the compiler
is broken (has a bug in that it is overzealous) or your program doesn't
conform or you've forgotten to tell the compiler that your program doesn't
conform in some way to the standard (F77 or F90 or whatever).

The compiler can rearrange statements if it determines that the results
will be exactly the same (computationally, not just mathematically) as if
they had been executed in the original order.

Besides compiler bugs, a typical problem resulting in a bug with such a
compiler is that your program isn't actually standard conforming, and you
might never find this out on traditional (non-vector) machines.  For
example:

    REAL A(100)
    CALL VADD(A(1),A(2),A(3),98)  !Add neighboring elements, store
                                  !in next element, to sum forward

    SUBROUTINE VADD(IN1,IN2,OUT,N)
    REAL IN1(N),IN2(N),OUT(N)
    DO I=1,N
       OUT(I) = IN1(I) + IN2(I)
    END DO
    END

(Please excuse any typos.)

This program should run fine on most traditional machines, but might
very well break on an optimizing compiler for a parallel machine.

Why?  Because the optimizer is allowed to assume it can read any element
of IN1 and IN2 before it writes any element of OUT in VADD, and that's
allowed because the arrays may not overlap according to the Fortran
standard (actual arguments may not overlap with each other or with
entities in common during a procedure call if the procedure or any
procedure it calls defines any entity involved in the overlap, is a
"simple" summary of the rule).

This surprising restriction (not found in any other common languages as far
as I know) specifically exists to provide supercomputers with the opportunity
for running most Fortran applications faster than would otherwise be
possible without the restriction.  You'd be surprised how much slower a
pipelined loop has to run to allow for overlapping arrays!

So, in summary, there shouldn't be a risk with statement-reordering
compilers, but in practice there is because the compiler might be too
agressive (have a bug) or your program violates some requirement that
the compiler imposes (from the standard) without notifying the compiler
of such a violation.  (I've heard some compilers, for example, provide
a directive that says "dummy arrays IN1, IN2, and OUT may overlap", which
can slow down execution but at least get the code to work.)

This is fun, but I've spent days tracking down "bugs" in the compiler I used
to work on that turned out to be exactly the kind of violation shown above.
One of the offenders was a 3rd-party vendor of math packages primarily for
supercomputers, written in Fortran (though because they may have fixed the
problem by know, I won't name them).

burley@world.std.com (James C Burley) (07/21/90)

In article <10074@brazos.Rice.edu> saltzman@mora.rice.edu (Matthew Saltzman) writes:

   In article <1990Jul20.153135.11273@ux1.cso.uiuc.edu> hirchert@ux1.cso.uiuc.edu (Kurt Hirchert) writes:
   >1. On the subject of functions with side effects:
   >
   >   a. Fortran allows functions with side effects.
   >   b. However, you are not allowed to use a function with a side effect if that
   >      side effect could change the value of any other expression or
   >      subexpression in the same statement.  (The one exception to this general
   >      rule is that in a statement of the form IF(<expression>)<statement>,
   >      a side-effect in <expression> _can_ affect <statement>.
   (A couple of other postings have asserted something similar.) 

   I'm sorry, but I don't see how a compiler can practically enforce such a 
   restriction.  *Any* time a variable appears as an argument to a function,
   it's a candidate for modification.  If I write
	   X = F(Y) + Y + Z
   how can the compiler know if Y is modified by F()?  F() doesn't need to
   even appear in the same source file as the statement.  Detection of the
   modification at run-time seems to be an unreasonable restriction on
   optimization.   F() could even modify Z, if Z appeared in COMMON.
   Am I missing something?

Yes, you are missing something quite simple: you are not allowed to write
such a statement in a standard-conforming program, but then again a standard-
conforming compiler is NOT required to detect such a statement and report it
as an error.

This restriction is just like the restriction that you can't reference a
variable without first defining it (no read before write or DATA of it);
if you try it, the compiler can do anything it wants. Some are nice and give
you warning messages, but they can't detect all cases of it and aren't
required to.

Almost anyone who hasn't stuck their foolish head in the world of interpreting
standards documents (as I have) can easily get confused by the wording
standards use to describe restrictions and requirements.  Standards are
basically like contracts and often suffer from the same deficiencies as far
as readability by the audience for whom they are intended!  (-:

   >   c. Fortran does not guarantee that your function with side-effects will be
   >      executed.  If the expression in which it appears can be evaluated without
   >      it, your processor is free to skip the execution of the function.  If
   >      there is a possibility of this occurring, whether or not your processor
   >      suppresses the execution of the function, the standard calls for you
   >      to consider the side-effects of the function to be undefined and
   >      prohibits your making use of them.  (Since the standard does not limit
   >      the methods the processor can use in determining the expression value
   >      without calling the function, it has been argued that you should always
   >      treat function side-effects as undefined.)

   This is a reasonable specification, but it is not the same as "not allowed."
   My Sun FORTRAN compiler has no problem with the above construct (with
   F(Y) modifying Y).  I understand that if I actually *did* do this, it 
   would be at my peril.

Well, in one sense "not allowed" can be taken to mean "doesn't work on my
machine".  But I think the sense of "not allowed" in the original posting
was "not allowed in a standard-conforming program".

   >   d. All of the above contributes to my recommendation that you not use
   >      functions with side-effects in Fortran.

   Yes!

Personally, I'm not sure that the standard even theoretically allows such
severe treatment of functions with side effects, but I may be wrong.  It
seems to me the spirit, if not the letter, of the F77 standard in this area
was to say "the compiler can avoid making function calls if it can determine,
by simply looking at only the program unit being compiled, that they are not
needed at compile or run time".  Now if a compiler looks at more than one
program unit at a time (truly global optimization) and decides to eliminate
function calls, then IMHO it must still perform any side effects coded for
that function unless it determines that they, too, can be eliminated on a
global basis.  In other words, it should perform those side effects "as if"
the function had been called if the removal of that function call is based
on partial (rather than complete) global optimization techniques.

   > [deleted]
   >Kurt W. Hirchert     hirchert@ncsa.uiuc.edu
   >National Center for Supercomputing Applications

	   Matthew Saltzman
	   saltzman@rice.edu

   Disclaimer: Institutions can't have opinions.

James Craig Burley   "Nor can opinions be considered institutions!" (-:

hirchert@ux1.cso.uiuc.edu (Kurt Hirchert) (07/22/90)

In article <BURLEY.90Jul21054349@world.std.com> burley@world.std.com (James C Burley) writes:
>Personally, I'm not sure that the standard even theoretically allows such
>severe treatment of functions with side effects, but I may be wrong.  It
>seems to me the spirit, if not the letter, of the F77 standard in this area
>was to say "the compiler can avoid making function calls if it can determine,
>by simply looking at only the program unit being compiled, that they are not
>needed at compile or run time".  Now if a compiler looks at more than one
>program unit at a time (truly global optimization) and decides to eliminate
>function calls, then IMHO it must still perform any side effects coded for
>that function unless it determines that they, too, can be eliminated on a
>global basis.  In other words, it should perform those side effects "as if"
>the function had been called if the removal of that function call is based
>on partial (rather than complete) global optimization techniques.

o  It is clear from talking with the people who wrote the FORTRAN 77 standard
   that their intent was to address only those side effects that might
   interfere with optimization, and that the primary example they had in mind
   was optimizing logical expressions involving .AND. and .OR..  Nevertheless,
   no limitation was placed on the methods by which a processor might determine
   the value of an expression without executing the function reference.  In
   subsequent official interpretation of FORTRAN 77, X3J3 considered the case
   of a "moralistic" optimizer that converted each reference to a function with
   effects into a reference to an equivalent function without side effects and
   concluded that such a processor was allowed by the rules of FORTRAN 77.
   (The "moralistic" optimizer was hypothetical.)

o  Note that the implication of this interpretation is _not_ to prohibit
   functions with side effects.  It merely renders the results of those side
   effects undefined and, by implication, prohibits the use of those side
   effects.  For example, a function could communicate with some lower-level
   function through a common block.  The changed value in the common block
   would be a side-effect.  This is permitted by FORTRAN 77.  What is not
   permitted (under this interpretation of the rules) is a subsequent reference
   to the value in the common block.

o  In other words, inadvertant side effects are permitted as long as they do
   not interfere with other parts of the same statement.  Intentional side
   effects should be coded as subroutines rather than functions.

o  I know of no Fortran compiler that takes full advantage of this dictum, but
   I have seen enough that come close, that I would say this dictum represents
   practical advice for portable programming as well as being an abstract
   restriction from the standard.

o  As others have noted, these restrictions apply to the programmer, not the
   compiler.  A compiler is free to support functions with side effects.  Just
   don't expect consistency in the handling of these side effects as you go
   from compiler to compiler.
-- 
Kurt W. Hirchert     hirchert@ncsa.uiuc.edu
National Center for Supercomputing Applications

sjc@key.COM (Steve Correll) (07/26/90)

In article <BURLEY.90Jul21054349@world.std.com>, burley@world.std.com (James C Burley) writes:
> ...It
> seems to me the spirit, if not the letter, of the F77 standard in this area
> was to say "the compiler can avoid making function calls if it can determine,
> by simply looking at only the program unit being compiled, that they are not
> needed at compile or run time".  Now if a compiler looks at more than one
> program unit at a time (truly global optimization) and decides to eliminate
> function calls, then IMHO it must still perform any side effects coded for
> that function unless it determines that they, too, can be eliminated on a
> global basis.

The F77 standard explicitly says the processor may omit to evaluate a function
reference if it doesn't need to know the return value, and that any entities
that would ordinarily have become defined by "side effects" instead become
undefined. See section 6.6.1, page 6-16 of ANSI X3.9-1978. The example in the
standard is:

	X .GT. Y .OR. L(Z)

where L is a logical function which defines its dummy argument. The standard
says that if X is greater than Y, then Z becomes undefined. Not very user-
friendly, but Fortran programmers have traditionally been tough as nails.
-- 
...{sun,pyramid}!pacbell!key!sjc 				Steve Correll

jlg@lanl.gov (Jim Giles) (07/27/90)

From article <2009@key.COM>, by sjc@key.COM (Steve Correll):
> [...]
> 	X .GT. Y .OR. L(Z)
> 
> where L is a logical function which defines its dummy argument. The standard
> says that if X is greater than Y, then Z becomes undefined. Not very user-
> friendly, but Fortran programmers have traditionally been tough as nails.

Since this started as a comparison to C, let's remember that C is just
as bad here.  You can't predict a-priori whether the function L() will
be executed in either language.  In pretty much any language, it's a
bad idea to have functions with side-effects in a context like this.

J. Giles

ansok@stsci.EDU (Gary Ansok) (08/01/90)

In article <58237@lanl.gov> jlg@lanl.gov (Jim Giles) writes:
>From article <2009@key.COM>, by sjc@key.COM (Steve Correll):
>> [...]
>> 	X .GT. Y .OR. L(Z)
>> 
>> where L is a logical function which defines its dummy argument. The standard
>> says that if X is greater than Y, then Z becomes undefined. Not very user-
>> friendly, but Fortran programmers have traditionally been tough as nails.
>
>Since this started as a comparison to C, let's remember that C is just
>as bad here.  You can't predict a-priori whether the function L() will
>be executed in either language.  In pretty much any language, it's a
>bad idea to have functions with side-effects in a context like this.

Well, sort of.  For the C equivalent

	(x > y) || l(&z)

you cannot tell just by looking at the statement whether l() will be
called or not.  However, you are guaranteed that if (x > y) is true,
then l() will NOT be called and if (x > y) is false, l() will be
called.

Fortran makes no such guarantees -- if (X .GT. Y) is false, L() must
be called, but if (X .GT. Y) is true, then L() MAY OR MAY NOT be
called, at the whim of the compiler.

I agree that functions with side-effects, especially in a context like
this, can be confusing and often lead to subtle bugs.  However, the
stop-as-soon-as-possible guarantee of C has its uses, and I certainly
prefer it to the whatever-the-compiler-feels-like to Fortran.

- Gary

-- Gary

sjc@key.COM (Steve Correll) (08/03/90)

In article <58237@lanl.gov>, jlg@lanl.gov (Jim Giles) writes:
> From article <2009@key.COM>, by sjc@key.COM (Steve Correll):
> > [...]
> > 	X .GT. Y .OR. L(Z)
> > 
> > where L is a logical function which defines its dummy argument. The standard
> > says that if X is greater than Y, then Z becomes undefined. Not very user-
> > friendly, but Fortran programmers have traditionally been tough as nails.
> 
> Since this started as a comparison to C, let's remember that C is just
> as bad here.  You can't predict a-priori whether the function L() will
> be executed in either language.

C is predictable. The Fortran standard says that the processor _need_ _not_
execute the function L if X exceeds Y, and that therefore the program must
assume Z is undefined. The C standard for "(x > y) || l(&z)" says that the
processor _must_ _not_ execute l if x exceeds y, so the program may therefore
assume z is unchanged.

I make no judgement about which definition is better. I didn't mean to
disparage Fortran in the first place, just to make clear that the Fortran 77
standard explicitly relieves the translator of the obligation of worrying about
side effects in this case, putting the onus on the programmer to avoid them.
-- 
...{sun,pyramid}!pacbell!key!sjc 				Steve Correll

jlg@lanl.gov (Jim Giles) (08/04/90)

From article <2022@key.COM>, by sjc@key.COM (Steve Correll):
> In article <58237@lanl.gov>, jlg@lanl.gov (Jim Giles) writes:
>> > 	X .GT. Y .OR. L(Z)
> [...]
> C is predictable. The Fortran standard says that the processor _need_ _not_
> execute the function L if X exceeds Y, and that therefore the program must
> assume Z is undefined. The C standard for "(x > y) || l(&z)" says that the
> processor _must_ _not_ execute l if x exceeds y, so the program may therefore
> assume z is unchanged.

I've recieved this response from several other people as well.  I was
going to handle the problem by email, but it keeps coming up.

C is predictable only if you know in advance whether X was greater than
Y.  If I knew that, I wouldn't have tested it.  This is what I meant
when I said that neither language is defined in such a way as to be
able to tell a priori (from the first) whether the function would be
evaluated or not.  This means that I can't optimize by doing the function
and the compare simultaneously (actually, in Fortran I _can_ optimize like
that, but the user can't portably rely on it).  It also means that I can't
apply the mathematical properties of the 'or' operator to correctness
proofs of the program.

J. Giles