HP3000-L Archives

December 1997, Week 1

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
Jerry Fochtman <[log in to unmask]>
Reply To:
Jerry Fochtman <[log in to unmask]>
Date:
Thu, 4 Dec 1997 07:04:21 -0600
Content-Type:
text/plain
Parts/Attachments:
text/plain (75 lines)
At 05:33 PM 12/3/97 -0500, Daniel Levite wrote:
>ANYONE KNOW THE TRICK AND ISSUES IN CALLING A FORTRAN SUBROUTINE FROM A
>COBOL PROGRAM?

Can you provide more information as to the arguments, and also which
FORTRAN compiler is being used (FORTRAN-66, FORTRAN-77, FORTRAN/iX)
as it will make a difference in terms of character string arguments.
Also, are you using CM or NM COBOL?

I'm going to speculate that perhaps one of the arguments is a character
string. When passing character strings to FORTRAN-77, it expects another
'hidden' argument behind each character string which is the string
length, passed by value.  For example (I think this example is
correct...it's been awhile  :-)

FORTRAN-77 Routine:

    SUBROUTINE FOO(string)
    CHARACTER string*80

when called in COBOL would be:

     01 STRING          PIC X(80)
         ....
     CALL FOO USING STRING, \80\.

There's also a FORTRAN compiler directives "$FTN66_3000 CHARS ON"
and "$FTN66_3000 CHARS OFF" which can be wrapped around the
SUBROUTINE statement and will remove the need to pass the string
length by value.  However, this also will mean that if any other
FORTRAN77 routines call this one, they too, will have to have this
compiler directive around the calls to this routine.

modified FORTRAN Routine:

$FTN66_3000 CHARS ON

    SUBROUTINE FOO(string)

$FTN66_3000 CHARS OFF

    CHARACTER string*80

now when called in COBOL would be:

     01 STRING            PIC X(80)
         ....
     CALL FOO USING STRING.

Its been sometime since I've had to worry about this so my memory may
be weak (read: wrong!).  However, this scenario is probably the first
thing I would check, as many times this is the problem when interfacing
to FORTRAN (especially 77) from other languages.  There definitely other
folks on this list who are more current in terms of COBOL knowledge....
I've primarily been working in C, GNU, PASCAL, SPL, SPLASH, and all 3 flavors
of FORTRAN the last several years.



/jf
                              _\\///_
                             (' o-o ')
___________________________ooOo_( )_OOoo____________________________________

                        Thursday, December 4th

            Today, in 1783 - George Washington retired as Commander-
                             in-Chief of the Continental Army.

___________________________________Oooo_____________________________________
                            oooO  (    )
                           (    )  )  /
                            \  (   (_/
                             \_)

ATOM RSS1 RSS2