[comp.sys.mac.digest] INFO-MAC Digest V6 #18

Moderators.Jon@SUMEX-AIM.Stanford.EDU, Dwayne@SUMEX-AIM.Stanford.EDU, (02/22/88)

INFO-MAC Digest          Monday, 22 Feb 1988       Volume 6 : Issue 18

Today's Topics:
                        all of those fortran bugs


----------------------------------------------------------------------

Date: 17 Feb 88 18:01:00 EST
From: <bouldin@ceee-sed.arpa>
Subject: all of those fortran bugs
Reply-to: <bouldin@ceee-sed.arpa>

 1: Date:  04-Nov-86 14:04 EST
 2: From:  David Sloan [76475,3012]
 3: Subj:  Absoft Fortran Bugs
 4:
 5: Mr. Bouldin,
 6:
 7: We are users of MS Fortran (V2.2) on a Macintosh Plus.
 8: We have experienced several problems with the compiler
 9: and would like to respond to your request to assemble
10: a list bugs. We would also appreciate a copy of your
11: current list of V2.2 bugs. If possible, could you please
12: forward this list via Compuserve to user id 76475, 3012.
13: Here are some of the more serious problems that we
14: have encountered:
15:
16: 1) Problem with incorrect array addressing for arrays
17:    with negative dimensions. The compiler assumes that
18:    the base address of the array corresponds to an index
19:    of 0.
20:       REAL X(0:N-1)
21:           .
22:           .
23:       CALL SUB (X, L, M)
24:           .
25:           .
26:       SUBROUTINE SUB (X, L, M)
27:       REAL X(-L:M)
28:           .
29:           .
30:       X(-1) = 0.0
31:           .
32:           .
33:    A location before the base of X will be overwritten.
34:
35: 2) Stack alignment is wrong after a call to a subroutine
36:    with many parameters. We have noticed problems calling
37:    a subroutine with 19 parameters.
38:
39: 3) Constant expressions don't seem to work in implied
40:    data statements. For example,
41:       PARAMETER (N=0, M=10)
42:       REAL X(1:10)
43:       DATA (X(I), I=N+1, M) /.../
44:    The N+1 term gives a compilation error.
45:
46: 4) A CHAR function in a parameter statement bombs the
47:    compiler. (Some compilers accept this construct.)
48:       CHARACTER TAB
49:       PARAMETER (TAB=CHAR(9))
50:
51: Please feel free to contact us by phone, or via
52: Compuserve. We do receive UUCP mail but I'm not
53: sure if we can send mail. The partial UUCP path is
54: bnr-mtl!bnr-vpa!utcs!utzoo and my Vax account is SLOAN.
55: My name, address, and phone number is:
56:
57:            David Sloan
58:        c/o Bell-Northern Research
59:            3 Place du Commerce
60:            Verdun, Quebec,
61:            Canada, H3E 1H6
62:            Telephone: (514) 765-7827
63:
64: Thank you for your time and effort.
65:
66:                  Regards,
67:
68:                     David
69:
Date: Fri, 3 Apr 87 15:52:50 CST
From: wmartin@ngp.utexas.edu (Wiley Sanders)
Subject: Fix for bug in Macfortran call to SIZERESOURCE

There is an error in the file "resource.inc" supplied
with MacFortran 2.2. The error is an incorrect value
for the trap code for SIZERESOURCE. The old, incorrect
value is: z'9A550000'. The correct value should be
z'9A590000'. Without this correction, calling SIZERESOURCE
will bomb. Credit goes to Dan Kampmeier, whose source to
McFace gives the correct value of the trap code.
-w

------------------------------

Date: Fri 3 Apr 87 17:57:10-PST
From: Tony Siegman  <SIEGMAN@Sierra.Stanford.EDU>
Subject: Complex Variables in MS Fortran

In Microsoft Fortran the mini-program
         DO 10 K=1,10
         A=CMPLX(1.0,0.0)+K
     10  WRITE (9,*) REAL(A),AIMAG(A)
will compile without errors and produce the output
         2.000  0.000
         3.000  0.000
          .....
while the miniprogram
         A0=CMPLX(1.0,0.0)
         DO 10 K=1,10
         A=A0+K
     10  WRITE (9,*) REAL(A),AIMAG(A)
will produce
         2.000  1.000
         3.000  2.000
         4.000  3.000
               .....
In both cases the compiler reports that A is real, and the locations of A
and K are four units apart.  I guess you have to be real careful when
specifiying and using complex variables in MS Fortran!

------------------------------
From: traffic@ut-ngp.UUCP (Wiley Sanders)
Subject: MacFortran: Bug or Feature?
Date: 28 Apr 87 06:20:06 GMT
Organization: UTexas Computation Center, Austin, Texas

There was something on the net a few days ago about a bug in the DATA
statement to the effect that, if a is real,

      DATA (a(i),i=1,5) / 200.3, 345.6, 378.5, 500, 456.6/

will return a zero in a(4) because the decimal point is missing. The bug
was said to be 'deep within the compiler' and not likely to be fixed in
subsequent releases.

I have encountered a problem similar to this in reading character files.
Reading the fields '345.67', or '3456.78' in F7.2 format works fine,
until a field missing a decimal point is encountered. Then, reading a
field like '2345' will result in 23.45 instead of 2345.00 being read
into the real variable. I am not sure whether this is a bug or not, as
the F77 spec is rather vague about what really should happen. But it's
enough that I'm giving up converting characters to reals with character
files; I wrote a subroutine to parse the string w.r.t.the decimal point
instead.
-w

------------------------------

From:	SDCVAX::MAILER       27-MAR-1987 17:00
To:	BOULDIN
Subj:	MS FORTRAN

Return-Path: <mcnabb@b.cs.uiuc.edu>
Received: from b.cs.uiuc.edu by CEEE-SED.ARPA ; 27 Mar 87 16:58:55 EST
Received: by b.cs.uiuc.edu (UIUC-5.52/9.7)
	id AA18007; Fri, 27 Mar 87 15:56:03 CST
Date: Fri, 27 Mar 87 15:56:03 CST
From: mcnabb@b.cs.uiuc.edu (David McNabb)
Message-Id: <8703272156.AA18007@b.cs.uiuc.edu>
To: bouldin@ceee-sed.arpa
Subject: MS FORTRAN

I've run into another non-feature of the new (V2.2) MSF system that
really should be fixed.  It does not seem to be possible to do screen
dumps while the debugger is running.  We teachers would like to make
and show slides on how to use the debugger.  (Luckily I made a few
such screen dumps last Spring using the old version of the compiler/
debugger, which DID allow screen dumps.  They look pretty much the
same as the new version, so I can use these in my lectures.)

I recently tried using the "Camera" DA which I picked up off the net.
This is supposed to allow you to set a timer, go off and run whatever
you want, and when the timer expires a screen dump occurs.  Camera
works while the compiler is running but not while the debugger is
running (does the debugger clear all events on startup???).  I wonder
if at least this much could be fixed to allow DAs to do snapshots.

If you still chat with MS/Absoft about their F77 system, please pass
this request along to them.  Thanks.

        David McNabb

        Department of Computer Science
        University of Illinois at Urbana-Champaign
        USENET:	...!{cmcl2,seismo,ihnp4}!uiucdcs!mcnabb
        ARPA:	mcnabb@a.cs.uiuc.edu
From:	SDCVAX::MAILER       27-MAR-1987 21:09
To:	BOULDIN
Subj:	Fortran 2.2 bug

Return-Path: <J.JJGH@OTHELLO.STANFORD.EDU>
Received: from OTHELLO.STANFORD.EDU by CEEE-SED.ARPA ; 27 Mar 87 21:09:06 EST
Date: Fri 27 Mar 87 18:05:29-PST
From: Jaime Gomez <J.JJGH@OTHELLO.STANFORD.EDU>
Subject: Fortran 2.2 bug
To: bouldin@CEEE-SED.ARPA
cc: jaime@SUMMIT
Message-ID: <12289857851.10.J.JJGH@OTHELLO.STANFORD.EDU>


Since you forwarded to Absoft the bug I posted about overlapping loops here
it is another one that I found with the Debugger and I guess it won't be
easy to fix.

The bug happens when using subroutines with dynamic dimension, i.e., when
the dimensions are dimesions are sent in the call to the subroutine and
the matrix has been dimesioned as matrix(1stdim, 2nddim,..., before-lastdim,1).
In this situation the matrix cannot be examined when within the subroutine
although all the computations are OK and the matrix can be examined when in
_MAIN. When I say that you cannot examine the matrix I mean that the values
displayed by the Debugger do not correspond at all with the values that must be.

Another problem, at least to be reported in the manual, is that all input
files must have and extra blank line at the end of them for the application
to detect the end of file. If that blank is not there, then the mac freezes,
no error report, nothing at all.

That's all

j.jjgh@othello.stanford.edu

-------
From:	SDCVAX::MAILER        4-NOV-1986 05:16
To:	BOULDIN
Subj:	Macintosh FORTRAN

Return-Path: <PDMMAC%MCMASTER.BITNET@WISCVM.WISC.EDU>
Received: from WISCVM.WISC.EDU by CEEE-SED.ARPA ;  4 Nov 86 05:16:21 EST
Received: from (PDMMAC)MCMASTER.BITNET by WISCVM.WISC.EDU on 10/31/86
  at 15:23:43 CST
Date:     Fri, 31 Oct 86 16:16 EDT
From:        <PDMMAC%MCMASTER.BITNET@WISCVM.WISC.EDU>
Subject:  Macintosh FORTRAN
To:  BOULDIN@CEEE-SED.ARPA
X-Original-To:  "BOULDIN@CEEE-SED.ARPA", PDMMAC

I noticed on a news file a few months ago (in Australia, actually) that you
were soliciting suggestions for a future release of Microsoft FORTRAN for the
Macintosh.

I have been using 2.1 and am impressed with the speed and convenience of
compilation, compared to Microsoft FORTRAN on the PC.  The execution time for
number-crunching compares very well with a PC and 8087, but is still slower
than Lahey-compiled PC code.  It is much faster than a PC without 8087.

Can you tell me when there will be a release that can be run from a Mac +
2-sided disk or a Hard Disk??

The other improvements I would recommend are to do with treatment of double
precision, and would make Mac FORTRAN behave in the same sensible way that
VMS FORTRAN does on the VAX.

1.In Mac FORTRAN,

FUNCTION FN(X)
IMPLICIT DOUBLE PRECISION (F,X)
FN=X*X

will not make FN double precision; you have to use, instead,

DOUBLE PRECISION FUNCTION FN(X)

I think that the IMPLICIT statement should also apply to the function.

2. Double precision constants should be recognized by their context and not
always need the D notation.  For example,

DOUBLE PRECISION A
A=0.
A=A+.1

should compile with .1 a double precision constant, since there is no question
that it ought to be.  Mac FORTRAN will not do this unless you write

A=A+.1D0

and this is tedious when converting an old program from single to double
precision.

Peter Macdonald
PDMMAC@MCMASTER.BITNET

From:	SDCVAX::MAILER        3-NOV-1986 09:27
To:	BOULDIN
Subj:	fortran flame

Return-Path: <patnaik@nrl-lcp.ARPA>
Received: from nrl-lcp.ARPA by CEEE-SED.ARPA ;  3 Nov 86 09:27:23 EST
Date: 2 Nov 86 17:12:00 EDT
From: "Gopal Patnaik" <patnaik@nrl-lcp.ARPA>
Subject: fortran flame
To: "bouldin" <bouldin@ceee-sed.arpa>
Reply-To: "Gopal Patnaik" <patnaik@nrl-lcp.ARPA>

I just read your post on info-mac today.  My biggest complaint with the
MS MAC FORTRAN compiler is the non-standard implementation of entries. Not
only is the implementation non-standard, any mistake in the order or number
or type of arguments is NOT flagged and leads to unpredictable results.
This was true in even the beta test version 2.2.  I know entries are archaic
(so is the programming style around here) but I would like the complier to
conform to the standard.  Could you pass this on?

Thanks.

Gopal Patnaik
patnaik@nrl-lcp.arpa
------
------
From: wmartin@ut-ngp.UUCP (Wiley Sanders)
Subject: Really Strange, Evil MacFortran Problem
Date: 7 Nov 86 00:46:32 GMT
Organization: UTexas Computation Center, Austin, Texas

Here is a really perplexing bug in MacFortran 2.2. I was trying to write
a simple program to calculate values of a poisson distribution, and dis-
covered that, in passing values to an external function, the values were
being trashed during the call to the external function, *regardless of
whether the parameters were touched (equated) in the function*. I was
trying to get the following program to work:

C This program does not work
C remove or comment out line 6 (the if/execute stmt) and it will work
      program tst
      real la
      integer j,m
      do 20 m=1,4
      la=480./3600.
      j=24
      if (m.EQ.-1) execute 'v2:MacFortran 2.2'
      write (9,fmt='(a,f14.2,2i20)') 'Bef Passing:',la,j,m
      write (9,fmt='(a,f14.2)') 'Val of bugger:',bugger(la,j,m)
  20  write (9,fmt='(a,f14.2,2i20)') 'Aft Passing:',la,j,m
      pause
      execute 'v2:macFortran 2.2'
      end

      real function bugger(lambda,i,m)
C just passes the factorial of the third parameter
      real lambda
      integer i,m
      write (9,100) 'bugger:',lambda,i,m
  100 format(a,f14.2,3x,2i20)
      bugger=real(ifact(m))
      return
      end

      integer function ifact(i)
C Compute Factorial
C  Param - i   Returns - i!
      integer i,k
      ifact=1
      IF (i.EQ.0) return
      do 5 k=1,i
    5  ifact=ifact*k
      return
      end

The values of la,j, and m in the main program were always trashed upon
returning from the function - but for the first time only! In addition
I noted that, even though m was trashed, usually to some large integer,
the program still counted the do loop correctly and called
the function 4 times. After two days worth of messing around, changing
random stuff here and there, lo and behold, upon removing line
6 (the if/execute line, a spurious line left over from a previous version
of the program that didn't work either, but accepted keyboard input and
was supposed to exit upon detecting an input value of -1), the following
program was created. It runs fine and the values are not trashed!

C This program works ok
C comment out line 6 (the if/execute stmt) and it will work
      program tst
      real la
      integer j,m
      do 20 m=1,4
      la=480./3600.
      j=24
C     if (m.EQ.-1) execute 'v2:MacFortran 2.2'
      write (9,fmt='(a,f14.2,2i20)') 'Bef Passing:',la,j,m
      write (9,fmt='(a,f14.2)') 'Val of bugger:',bugger(la,j,m)
  20  write (9,fmt='(a,f14.2,2i20)') 'Aft Passing:',la,j,m
      pause
      execute 'v2:MacFortran 2.2'
      end

      real function bugger(lambda,i,m)
(EXACTLY the same as above)
      return
      end

      integer function ifact(i)
(EXACTLY the same as above)
      return
      end

I know that MacFortran is extraordinarily sensitive to nulls and other
spurious characters that sometimes end up in a source file, but I looked
at the first file with FEdit and there are none -the file is clean.
   What gives? Is MacFortran incapable of handling external functions?
Anybody else have this problem? Someone should try clipping the first
listing above and see is it works - maybe there is something wrong with
my particular copy or something.
   Meanwhile, I will valiantly try to find a workaround, But it's kind of
like trying to find a workwround when you add 2+2 and get 5.

   %*!&^&#*!

-Wiley Sanders
 wmartin@ngp.UTEXAS.EDU
                           MacFortran 2.2 Bug

Date: Wed, 5 Nov 86 20:46:28 CST
From: wmartin@ngp.utexas.edu (Wiley Sanders)
Subject: MacFortran 2.2 Bug
Sender:
Reply-to: ngp!wmartin@ngp.utexas.edu (Wiley Sanders)

I am experiencing a rather frustrating bug with MacFortran 2.2, using external
functions. I have found that upon calling an external function:
      Z=FOO(A,B,C)
where
      REAL FUNCTION FOO(D,E,F)
      FOO=D+E+F  (etc etc)
and D,E, and F are not changed in the external function, that, upon return-
ing from the external function, the values of A,B, and C have been trashed
in the main program. This happens when the function is called the first time,
but not thereafter. I have a more detailed example program available if some-
one will contact me by mail, we can discuss this.
-w
Wiley Sanders
wmartin@ut-ngp.UTEXAS.EDU
Just when you thought it might be safe to use Absoft/Microsoft Fortran....

Here are 3 new bugs, two of them quite serious:

1. The ENTRY statement is not supported as specified by ANSI standard.
   Basically, all ENTRY points in a given subroutine must have the same
   number and type of arguments. This is NOT listed in the appendix that lists
   departures from the standard, it is NOT flagged during compilation. The
   code compiles and runs, it just runs incorrectly. How thoughtful. There
   are several work-arounds. My suggestion is just to break everything up
   into separate modules. Ugh.

2. Code like this:
      DO 10 I=1,NBLK
      L=MIN(I*128,NW)
   10 WRITE(IOUNIT,rec=I+PRU-1)(ARRAY(J),J=I*128-127,L)

   Will almost certainly run wrong. The external do loop and the implied do
   in the WRITE statement get in each others way. The external do is ALWAYS
   executed only ONCE, regardless of the value of NBLK. Double plus ungood.
   Solution: terminate the do loop with a CONTINUE statement.

3. The linker, while much improved, has a bug writing out the linked program.
   There is an error in the use of PBRename, so you can only output a linked
   file to the *same* directory as that in which the linker resides. It does
   work, but this is a nuisance.

Hope this stuff saves someone else all the frustration that I have been thru
over the past few days tracking this stuff down. We sure could use some more
vendors of Fortran compilers.
From: wmartin@ut-ngp.UUCP (Wiley Sanders)
Subject: Fix to Microsoft Fortran SIZERESOURCE bug.
Date: 3 Apr 87 21:57:41 GMT
Organization: UTexas Computation Center, Austin, Texas

There is an error in the file "resource.inc" supplied with MacFortran
2.2 that causes a bomb whenever SIZERESOURCE is called. The error is in
the PARAMETER statement specifying  the trap code for SIZERESOURCE. The
old, incorrect value is z'9A550000'. The correct value should be
z'9A590000'.
   Credit is due to Dan Kampmeier on this, who includes the correct vaue
in the source for his program "McFace." -w

From: wmartin@ut-ngp.UUCP (Wiley Sanders)
Subject: YA MacFortran Bug - TRIM(), blanks, and relational exp...
Date: 16 Apr 87 07:20:51 GMT
Organization: UTexas Computation Center, Austin, Texas

Well, here's another bug in MacFortran 2.2, and its workaround. This
time it's our good friend, the TRIM intrinsic function. Mac- Fortran
doesn't seem to like using TRIM in a character relational expression
when the argument to TRIM is all blanks. It hangs, forcing you to hit
the panic button. The bug manifests itself in the following sample
program, which reads the first line of a file, and checks if the first
line is equal to the character expression 'DISAGG':

      program sertst
      character*80 header,trim
      integer ios
      logical isdisagg
      character*256 inpfile
      write(9,1000) 'Enter Filename'
      read (9,1000) inpfile
C Open file
      open(1,file=inpfile,iostat=ios,status='OLD')
C Check if first line of file is the character string 'DISAGG'
      read(1,9000) header
      isdisagg=(trim(header).eq.'DISAGG')   ! <- Dies On This Line
      if (.not.isdisagg) stop 'not disagg'
      pause 'Done'
 9000 format(a80)
 1000 format(a)
      end

Most of the time, the program works fine. But when it opens a file whose
first line consists only of blanks, or only a CR, it hangs. It goes
ahead and pads out the character variable 'header' with 80 blanks, but
it will never return from the indicated line. A workaround that works OK
is:
      character*80 header
      character*6 tstdis
    - etc -
      tstdis=trim(header)          ! this works ok. Sigh.
      isdisagg=tstdis.eq.'DISAGG'
      if (.not.isdisagg) stop 'not disagg'
    - etc -

Which points the finger at using TRIM in the character relational
expression. TRIM seems to work OK otherwise, in assignment and in
iolists.

Phfbltfft!
-w
--
Wiley Sanders, Civil Engineering Dept, UT-Austin
secret NSA CIA anti Soviet Iran terrorist nuclear drug decoder ring
                                     - take THAT, NSA line-eater!
From: remym@tekig5.TEK.COM (Remy Malan)
Subject: Funny behaviour while using MS FOTRAN v2.2
Date: 4 Feb 87 18:33:54 GMT
Organization: Tektronix Inc., Beaverton, Or.

I have noticed something strange regarding MS FORTRAN's (v2.2) handling
of REAL*8 FUNCTIONS.  i.e. The compiler *seems* to generate bad code from
my examination of the assembly listings of the program.

I have included a sample pgm. to test the real*8 function call.  I have
yet to make this call work w/ MS FORTRAN although I did verify the code
worked on another computer.  (In fact, the original code that I was
working on was tested on two other computers and found to be right on both
of those.  Only on the Mac did I have problems.)

If some kind soul could verify my results or, better, tell me what I did
wrong w.r.t. the MS compiler, I would appreciate an e-mail reply.  If you
do verify this strange behaviour and would like to talk to MS, their
product support number is: (206)-882-8089.

Yours truly,
A. Remy Malan
ph: (503)-627-4184

----------------------------------------------------
Here is the code (assembly fragment follows source):

C
C   TEST PROGRAM FOR STRANGE BEHAVIOUR IN
C   MS FORTRAN V2.2
C   WRITTEN BY A. REMY MALAN  2/4/87
C
	PROGRAM TEST
	REAL*8 SUM
C
C   USE THE ASSEMBLY LISTING OPTION TO EXAMINE THE ASM
C   CODE FOR THE NEXT FORTRAN LINE.  I SAW A "JSR  140(A4)"
C   WHICH IS CONVERT SINGLE TO DOUBLE!  THAT
C   MAKES IT SEEM THAT THE COMPILER THINKS THAT FOOB()
C   IS A REAL*4 WHEN IN FACT IT IS DECLARED AS REAL*8!
C
    	SUM = FOOB()
C
C
	PRINT *, 'TEST: SUM = ',SUM
	PRINT *, 'HIT <CR> TO QUIT...'
	PAUSE
	
  	STOP
	END



	REAL*8 FUNCTION FOOB()
	REAL*8 P
	
	P = 25.0D+00
	PRINT *, 'FOOB: P = ',P
  	FOOB=P
	
	RETURN
	END

--------- end of FORTRAN ---------

Here is the assembler listing for the "sum=foob()" line:
Note the "jsr  140(a4)" line!  This, according to the manual,
is an intrinsic function call, CVTFL.

;         SUM = FOOB()

        MOVE.L  #.FOOB-L00003,D1
L00003: JSR     L00003(PC,D1.L)
        MOVEA.L A7,A3
        JSR     140(A4)		;This is convert single to double! - ARM
        MOVEM.L D0/D1,(A3)

--------- end of ASM fragment ---------
From:	SDCVAX::MAILER       20-OCT-1986 14:04
To:	BOULDIN
Subj:	ABSoft Fortran

Return-Path: <OR.LUSTIG@Sierra.Stanford.EDU>
Received: from Sierra.Stanford.EDU by CEEE-SED.ARPA ; 20 Oct 86 14:04:32 EDT
Date: Mon 20 Oct 86 11:04:03-PDT
From: Irvin Lustig <OR.LUSTIG@Sierra.Stanford.EDU>
Subject: ABSoft Fortran
To: bouldin@CEEE-SED.ARPA
Message-ID: <12248351458.17.OR.LUSTIG@Sierra.Stanford.EDU>

A friend of mine has version 1.0.  I tried to have a program with
multiple subroutines in each file.  The linker would not recognize
the external symbols correctly.  This was true for the first version
of MicroSoft Fortran as well.  I have not checked if this was fixed
in later versions.

As an example:

File name: MAIN     File name: SUB2
Main Program        Subroutine SUB2
Subroutine SUB1     Subroutine SUB3

SUB2 and SUB3 can't call SUB1, nor can the main program or SUB1 call SUB3.

Has this bug been fixed?  I have a 10000 line program in 5 files that
I want to port to the Mac.  It has about 200 or so subroutines.  I don't
want to split it up into 200 files.  If the bug hasn't been fixed, it
really needs to be.

Thanks in advance for your info.

-Irv Lustig
or.lustig@su-sierra.arpa         (Old way)
or.lustig@sierra.stanford.edu    (New way)
-------
I have noticed something strange regarding MS FORTRAN's (v2.2) handling
of REAL*8 FUNCTIONS.  i.e. The compiler *seems* to generate bad code from
my examination of the assembly listings of the program.

I have included a sample pgm. to test the real*8 function call.  I have
yet to make this call work w/ MS FORTRAN although I did verify the code
worked on another computer.  (In fact, the original code that I was
working on was tested on two other computers and found to be right on both
of those.  Only on the Mac did I have problems.)

If some kind soul could verify my results or, better, tell me what I did
wrong w.r.t. the MS compiler, I would appreciate an e-mail reply.  If you
do verify this strange behaviour and would like to talk to MS, their
product support number is: (206)-882-8089.

Yours truly,
A. Remy Malan
ph: (503)-627-4184

----------------------------------------------------
Here is the code (assembly fragment follows source):

C
C   TEST PROGRAM FOR STRANGE BEHAVIOUR IN
C   MS FORTRAN V2.2
C   WRITTEN BY A. REMY MALAN  2/4/87
C
        PROGRAM TEST
        REAL*8 SUM
C
C   USE THE ASSEMBLY LISTING OPTION TO EXAMINE THE ASM
C   CODE FOR THE NEXT FORTRAN LINE.  I SAW A "JSR  140(A4)"
C   WHICH IS CONVERT SINGLE TO DOUBLE!  THAT
C   MAKES IT SEEM THAT THE COMPILER THINKS THAT FOOB()
C   IS A REAL*4 WHEN IN FACT IT IS DECLARED AS REAL*8!
C
        SUM = FOOB()
C
C
        PRINT *, 'TEST: SUM = ',SUM
        PRINT *, 'HIT <CR> TO QUIT...'
        PAUSE

        STOP
        END



        REAL*8 FUNCTION FOOB()
        REAL*8 P

        P = 25.0D+00
        PRINT *, 'FOOB: P = ',P
        FOOB=P

        RETURN
        END

--------- end of FORTRAN ---------

Here is the assembler listing for the "sum=foob()" line:
Note the "jsr  140(a4)" line!  This, according to the manual,
is an intrinsic function call, CVTFL.

;         SUM = FOOB()

        MOVE.L  #.FOOB-L00003,D1
L00003: JSR     L00003(PC,D1.L)
        MOVEA.L A7,A3
        JSR     140(A4)         ;This is convert single to double! - ARM
        MOVEM.L D0/D1,(A3)

--------- end of ASM fragment ---------

From: traffic@ut-ngp.UUCP (Wiley Sanders)
Subject: MacFortran 'include' sensitive to trailing blanks...
Date: 22 Apr 87 06:09:14 GMT
Organization: UTexas Computation Center, Austin, Texas

the 'include' statement is sensitive to trailing blanks! in other words,
"include file.inc___" will cause an include file not found error to
occur even if the file 'file.inc' is present on disk.
  You can use the 'zap gremlins' feature of QUED to abolish trailing
blanks. sigh -w

------------------------------

End of INFO-MAC Digest
**********************