help-octave
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

Re: Fortran in Octave


From: Paul Kienzle
Subject: Re: Fortran in Octave
Date: Sun, 21 Mar 2004 23:32:53 -0500


On Mar 21, 2004, at 10:43 PM, address@hidden wrote:

On Sat, 20 Mar 2004 08:05 am, A S Hodel wrote:
I'd suggest that you look in the liboctave directory where Octave calls
the LAPACK fortran routines.
That will take  care of the fortran-specific issues in calling fortran
from C++.  The rest would be standard .oct file implementation.

If I remember right, you should look for the F77_FUNCTION macro
definition.

That's right.  I'll add that there are more helpful examples in src/
DLD-FUNCTIONS.  Particularly balance.cc and qz.cc.

For example, say the Fortran file tnine.f is

---tnine.f
      SUBROUTINE TNINE (IOPT, PARMOD, PS, X, Y, Z, BX, BY, BZ)
      INTEGER IOPT
      DOUBLE PRECISION PARMOD(10), PS, X, Y, Z, BX, BY, BZ

C     This is just a test subroutine body, to check connexions.
C     Put the sum of PARMOD in PS, and X, Y, Z into BX, BY, BZ

      INTEGER I

      PS = 0D0
      DO 1 I=1, 10
         PS = PS + PARMOD (I)
 1    CONTINUE

      BX = X
      BY = Y
      BZ = Z

      END
---end tnine.f

A minimal C++ wrapper would look like:

---t96.cc
#include <octave/oct.h>
#include "f77-fcn.h"

extern "C"
{
  int F77_FUNC (tnine, TNINE) (const int& IOPT, const double* PARMOD,
                                 double& PS,
                                 const double& X, const double& Y,
                                 const double &Z,
                                 double& BX, double& BY, double& BZ );
}

DEFUN_DLD (t96, args, ,
           "- Loadable Function: [PS, BX, BY, BZ] = t96 (PM, X, Y, Z)\n\
\n\
Returns the sum of PM in PS and X, Y, and Z in BX, BY, and BZ.")
{
  octave_value_list retval;

  const int dummy_integer = 0;
  Matrix pm;
  const double x = args(1).double_value(), y = args(2).double_value(),
    z = args(3).double_value();
  double ps, bx, by, bz;

  pm = args(0).matrix_value ();

  F77_XFCN (tnine, TNINE,
            (dummy_integer, pm.fortran_vec(), ps, x, y, z, bx, by, bz) );

  if (f77_exception_encountered)
    {
      error ("unrecoverable error in t96");
      return retval;
    }

  retval(0) = octave_value (ps);
  retval(1) = octave_value (bx);
  retval(2) = octave_value (by);
  retval(3) = octave_value (bz);
  return retval;
}
--end t96.cc

Compile this (in the Bourne Again Shell) with

$ mkoctfile t96.cc tnine.f

and run it in Octave like:

octave> [p, x, y, z] = t96 (1:10, sqrt (2), pi, e)
p = 55
x = 1.4142
y = 3.1416
z = 2.7183

There are a couple more points to add:

Use the above:

        F77_XFCN (name, NAME, (args...));
        if (f77_exception_encountered) ...

if you don't trust your fortran routine with all inputs you
give it.  Otherwise, you can use:

        F77_FUNC(name,NAME)(args...);

Octave was recently extended to support new architectures,
(Cray and visual fortran in particular), so the fortran interface
has been refined.

Use "F77_RET_T" instead of "int" for the return type when
declaring fortran functions.

Rather than using "const char*" for string argument declarations
and one extra "int" declaration at the end for each string length,
you now need either
        F77_CHAR_ARG_DECL
or
        F77_CONST_CHAR_ARG_DECL
depending on the const-ness of the argument, and
        F77_CHAR_ARG_LEN_DECL
at the end of the declarations.

To call a function with a string argument, you now need to use
one of the following in place of the string argument:

        F77_CHAR_ARG(x)
                non-const arg, len = strlen(x)
        F77_CONST_CHAR_ARG(x)
                const arg, len = strlen(x)
        F77_CXX_STRING_ARG(x)
                const arg, len = x.lenth()
        F77_CHAR_ARG2(x,n)
                non-const arg, len = n
        F77_CONST_CHAR_ARG2(x,n)
                const arg, len = n

No matter which of these you use, you need to use

        F77_CHAR_ARG_LEN(n)

at the end, which sometimes may be ignored.

String arguments are declared using:

        F77_FUNC(name,NAME) (..,
                F77_CONST_CHAR_ARG_DECL, ...,
                F77_CHAR_ARG_LEN_DECL)

with one arg len decl for each char arg.

There is also a macro for:

        F77_RETURN(retval)

which I'm guessing is for callbacks to fortran functions.

Paul Kienzle
address@hidden

---
PS,  please add this info to the octave wiki at

        http://wiki.octave.org/wiki.pl?OctaveFortran

I would do it myself, but the wiki is yet again not responding.



-------------------------------------------------------------
Octave is freely available under the terms of the GNU GPL.

Octave's home on the web:  http://www.octave.org
How to fund new projects:  http://www.octave.org/funding.html
Subscription information:  http://www.octave.org/archive.html
-------------------------------------------------------------



reply via email to

[Prev in Thread] Current Thread [Next in Thread]