[comp.lang.fortran] f2c bug

piner@maxwell.physics.purdue.edu (Richard Piner) (04/05/91)

Looks like I have found a little bug in f2c. Of course, it took a
routine from NR to break it. Here it is. Always double check code
before using it.

      SUBROUTINE QUAD3D(X1,X2,SS)
c you will need to add an explicit declaration of real here.
c      real H
      EXTERNAL H
      CALL QGAUSX(H,X1,X2,SS)
      RETURN
      END
C     
      FUNCTION F(ZZ)
      EXTERNAL FUNC
      COMMON /XYZ/ X,Y,Z
      Z=ZZ
      F=FUNC(X,Y,Z)
      RETURN
      END
C     
      FUNCTION G(YY)
      EXTERNAL Z1,Z2,F
      COMMON /XYZ/ X,Y,Z
      Y=YY
      CALL QGAUSZ(F,Z1(X,Y),Z2(X,Y),SS)
      G=SS
      RETURN
      END
C     
      FUNCTION H(XX)
      EXTERNAL Y1,Y2,G
      COMMON /XYZ/ X,Y,Z
      X=XX
      CALL QGAUSY(G,Y1(X),Y2(X),SS)
      H=SS
      RETURN
      END
------------------------------
f2c puts out the following code:
------------------------------
/* quad3d.f -- translated by f2c (version of 7 December 1990  17:37:08).
   You must link the resulting object file with the libraries:
	-lF77 -lI77 -lm -lc   (in that order)
*/

#include "/c/optics/F2c/f2c.h"

/* Common Block Declarations */

struct {
    real x, y, z;
} xyz_;

#define xyz_1 xyz_

/* Subroutine */ int quad3d_(x1, x2, ss)
real *x1, *x2, *ss;
{
/* h_() should be declared real !!!!! */
    extern /* Subroutine */ int h_();
    extern /* Subroutine */ int qgausx_();

/*      real H */
    qgausx_(h_, x1, x2, ss);
    return 0;
} /* quad3d_ */


doublereal f_(zz)
real *zz;
{
    /* System generated locals */
    real ret_val;

    /* Local variables */
    extern doublereal func_();

    xyz_1.z = *zz;
    ret_val = func_(&xyz_1.x, &xyz_1.y, &xyz_1.z);
    return ret_val;
} /* f_ */


doublereal g_(yy)
real *yy;
{
    /* System generated locals */
    real ret_val, r__1, r__2;

    /* Local variables */
    extern doublereal f_(), z1_(), z2_();
    static real ss;
    extern /* Subroutine */ int qgausz_();

    xyz_1.y = *yy;
    r__1 = z1_(&xyz_1.x, &xyz_1.y);
    r__2 = z2_(&xyz_1.x, &xyz_1.y);
    qgausz_(f_, &r__1, &r__2, &ss);
    ret_val = ss;
    return ret_val;
} /* g_ */


doublereal h_(xx)
real *xx;
{
    /* System generated locals */
    real ret_val, r__1, r__2;

    /* Local variables */
    extern doublereal g_(), y1_(), y2_();
    static real ss;
    extern /* Subroutine */ int qgausy_();

    xyz_1.x = *xx;
    r__1 = y1_(&xyz_1.x);
    r__2 = y2_(&xyz_1.x);
    qgausy_(g_, &r__1, &r__2, &ss);
    ret_val = ss;
    return ret_val;
} /* h_ */

mwm@VACATION.VENARI.CS.CMU.EDU (Mark Maimone) (04/06/91)

In article <4846@dirac.physics.purdue.edu>, piner@maxwell.physics.purdue.edu (Richard Piner) writes:
|> Looks like I have found a little bug in f2c. Of course, it took a
|> routine from NR to break it. Here it is. Always double check code
|> before using it.

  [code illustrating REAL FUNCTION H being referenced before declared]

F2c compiles functions one at a time, sequentially.  During the first pass through the program, since H has only been declared EXTERNAL, f2c assumes that it refers to a subroutine rather than a function; how could it infer anything else?  Fortunately, there is a mechanism for handling this situation (forward-referencing within a single file).  Run f2c once with the -P option; this will generate a prototype file.  Then run it again, naming both foo.f and foo.P on the command line.  You'll find that it corre









ctly types H as a doublereal function.

	% f2c -P foo.f
	  .
	  .
	Rerunning "f2c -P ... foo.f foo.P" may change prototypes or declarations
	% f2c -P foo.f foo.P
	  .
	  .
	% grep h_ foo.c	
	    extern doublereal h_();
	    qgausx_((E_fp)h_, x1, x2, ss);
	doublereal h_(real *xx)
	} /* h_ */

	% man f2c
		   ..............................................  File
	     names that end with `.p' or `.P' are taken to be prototype
	     files, as produced by option `-P', and are read first.
		   ...............................................

Looks like you have found a little idiosyncracy of Fortran.  Always read the man page before using software.
-- 
----------------------------------------------------------------------
Mark Maimone				phone: (412) 268 - 7698
Carnegie Mellon Computer Science	email: mwm@cs.cmu.edu
grad student, vocal jazz and PDQ Bach enthusiast

chidsey@smoke.brl.mil (Irving Chidsey) (04/06/91)

In article <1991Apr5.175633.18864@cs.cmu.edu> mwm@VACATION.VENARI.CS.CMU.EDU (Mark Maimone) writes:
<In article <4846@dirac.physics.purdue.edu>, piner@maxwell.physics.purdue.edu (Richard Piner) writes:
<|> Looks like I have found a little bug in f2c. Of course, it took a
<|> routine from NR to break it. Here it is. Always double check code
<|> before using it.
<
<
<Looks like you have found a little idiosyncracy of Fortran.  Always read the man page before using software.
<-- 
<----------------------------------------------------------------------
<Mark Maimone				phone: (412) 268 - 7698
<Carnegie Mellon Computer Science	email: mwm@cs.cmu.edu
<grad student, vocal jazz and PDQ Bach enthusiast

	Double check the code!  Read the man pages!  What novel ideas!

	Where is your spirit of adventure?

								Irv

-- 
I do not have signature authority.  I am not authorized to sign anything.
I am not authorized to commit the BRL, the DA, the DOD, or the US Government
to anything, not even by implication.  They do not tell me what their policy 
is.  They may not have one.		Irving L. Chidsey  <chidsey@brl.mil>

burley@albert.gnu.ai.mit.edu (Craig Burley) (04/06/91)

In article <4846@dirac.physics.purdue.edu> piner@maxwell.physics.purdue.edu (Richard Piner) writes:

   Looks like I have found a little bug in f2c. Of course, it took a
   routine from NR to break it. Here it is. Always double check code
   before using it.

	 SUBROUTINE QUAD3D(X1,X2,SS)
   c you will need to add an explicit declaration of real here.
   c      real H
	 EXTERNAL H
	 CALL QGAUSX(H,X1,X2,SS)
	 RETURN
	 END
   [...]
   ------------------------------
   f2c puts out the following code:
   ------------------------------
   /* quad3d.f -- translated by f2c (version of 7 December 1990  17:37:08).
      You must link the resulting object file with the libraries:
	   -lF77 -lI77 -lm -lc   (in that order)
   */

   #include "/c/optics/F2c/f2c.h"

   /* Subroutine */ int quad3d_(x1, x2, ss)
   real *x1, *x2, *ss;
   {
   /* h_() should be declared real !!!!! */
       extern /* Subroutine */ int h_();
       extern /* Subroutine */ int qgausx_();

   /*      real H */
       qgausx_(h_, x1, x2, ss);
       return 0;
   } /* quad3d_ */
   [...]

I don't believe it is required by the ANSI standard or by most C
implementations for h_() to be declared real.  In other words, I don't
see why this is a bug.  An inconsistency, perhaps, given the (omitted)
example of a backward reference working, but that is not really the realm
of Fortran as much as UNIX and C (the way UNIX, vs. other systems, handles
object files, and the way C, vs. Fortran, handles putting multiple
procedures in a source file).

From my reading of the standard, it is ambiguous in QUAD3D whether H is
a subroutine or function by examination of QUAD3D alone.

If anyone interprets the standard differently, please let me know where you
find the critical text.  I thought I could find it, but after 10 minutes of
searching, I couldn't.  Certainly the standard plainly says it is ambiguous
if H was passed in as a dummy argument, declared EXTERNAL, and passed back
out again.  But here, H is not a dummy, and yet appears to still be
ambiguous according to the standard.  (My own fortran front end agrees with
this...funny how I can't remember something I've already implemented, so I
ask my old code by running it!)

And, I believe, it won't matter whether h_() is declared int (subroutine),
real, double, or any other function type, in QUAD3D's C-code implementation,
because only a pointer to the procedure is passed, and it is up to the
procedure that actually calls the dummy containing a pointer to h_() to
declare it properly.  Maybe some C implementations will have a problem with
this, but I don't know of any.  (It probably violates the ANSI C standard,
for example, but if that's the case, there's no way I know for f2c to fully
handle the situation without multiple passes with prototypes, as another
responder has mentioned.)

Note that I think it is wise in such cases to add the "REAL H" as
indicated by the comment line.  It shouldn't really matter to a good
compiler (assuming I'm correct above), but it can make code maintenance
a lot easier.
--

James Craig Burley, Software Craftsperson    burley@ai.mit.edu