%VAL in NAG Fortran Compiler?

I am currently looking into the NAG Fortran Compiler for apple silicon, previously only working with ifort more or less, but I immediately stumble with finding a suitable replacement for %VAL.

Mathworks use this workaround (as an example), but it seems less than ideal:

#ifdef NAGFOR
      allocate(tpr_in(size, 1))
      allocate(tpr_out(size, 1))
      call mxcopyptrtoreal8(pr_in, tpr_in, size)
      call compute(tpr_out, tpr_in, size)
      call mxcopyreal8toptr(tpr_out, pr_out, size)
#else
      call compute(%VAL(pr_out), %VAL(pr_in), size)
#endif

If I am not mistaken, you could use the ‘value’ attribute in the declaration of the arguments of your compute subroutine. Assuming that you have access to that subroutine.
This is from the IBM documentation

The VALUE attribute specifies an argument association between a dummy and an actual argument. This association allows you to pass the dummy argument with the value of the actual argument. This Fortran 2003 pass by value implementation provides a standard conforming option to the %VAL built-in function.

2 Likes

The %VAL() function suggests that both arguments are input, but the NAGFOR block suggests that the first argument is output.

Is the compute routine a Fortran routine you wrote or is it some MATLAB routine? If you do not have control over its actual implementation, but know that the first argument is supposed to be an address and the second is a value, then you could define the interface as:

interface
    subroutine compute( out, in, size )
    real(kind=8) :: out
    real(kind=8), value :: in
    integer, value :: size
   end subroutine
end interface

or something similar. (And in the above I was too lazy to use a proper KIND for the real - you should not “8” of course)

A minimum (non-working) example, after trying the VALUE attribute:

#include "fintrf.h"
C=======================================================================
C
C=======================================================================
      MODULE FSIN
      CONTAINS
      SUBROUTINE MEXFUNCTION(nlhs, plhs, nrhs, prhs)
C
      IMPLICIT NONE
C
      INTEGER*8 :: plhs(*), prhs(*)
      INTEGER*4 :: nlhs, nrhs
C
      INTEGER*8 :: mxGetPr
      INTEGER*8 :: mxGetM
      INTEGER*8 :: mxGetN
C
      INTEGER*8 :: X_PTR, Y_PTR
      INTEGER*8 :: M, N
C
C-----------------------------------------------------------------------
C
C     GET THE SIZE OF THE INPUT X.
      M = mxGetM(prhs(1))
      N = mxGetN(prhs(1))
C
C     GET POINTERS FROM THE INPUT ARGUMENTS.
      X_PTR = mxGetPr(prhs(1))
      Y_PTR = mxGetPr(prhs(2))
C
C     CALL THE COMPUTATIONAL ROUTINE.
      CALL COMPUTE(Y_PTR, X_PTR, M, N)
C
C
      RETURN
      END
C
C
C=======================================================================
C
      SUBROUTINE COMPUTE(Y, X, M, N)
C
      IMPLICIT NONE
C
      INTEGER*8, INTENT(IN) :: M, N
      REAL*8, VALUE         :: X(M, N)
      REAL*8, VALUE         :: Y(M, N)
C ----------------------------------------------------------------------
C
      Y = SIN(X)
C
      RETURN
      END
      END MODULE FSIN
C
C ----------------------------------------------------------------------
C ----------------------------------------------------------------------
C
C
C

Yes, upper case is not needed, but only fixed format is supported by the pre-processor in this case; same with the integer8 and real8 etc.

It complains about the integer ↔ mismatch and scalar ↔ array mismatch.
I haven’t used the value attribute previously, so I guess there is some simple error?
Originally it complained about the lack of an explicit interface so I added MODULE.

Original version, working with the Intel Fortran Compiler:

#include "fintrf.h"
C=======================================================================
C
C=======================================================================

      SUBROUTINE MEXFUNCTION(nlhs, plhs, nrhs, prhs)
C
      IMPLICIT NONE
C
      mwPointer :: plhs(*), prhs(*)
      INTEGER*4 :: nlhs, nrhs, AVOIDW
C
      mwPointer :: mxGetPr
      mwPointer :: mxCreateDoubleMatrix
      mwPointer :: mxGetM
      mwPointer :: mxGetN
C
      mwPointer :: X_PTR, Y_PTR
      mwSize    :: M, N
C
C-----------------------------------------------------------------------
      AVOIDW = nlhs + nrhs ! USE VARIABLES TO AVOID UNUSED WARNING
C
C     GET THE SIZE OF THE INPUT ARRAY.
      M = mxGetM(prhs(1))
      N = mxGetN(prhs(1))
C
C
C     CREATE FORTRAN ARRAY FROM THE INPUT ARGUMENT.
      X_PTR = mxGetPr(prhs(1))
C
C
      IF (nrhs > 1) THEN
C       USE SUPPLIED ARGUMENT
        Y_PTR = mxGetPr(prhs(2)) ! OUTPUT DATA, Y
        IF (M*N < 2.0) THEN
          CALL mexErrMsgIdAndTxt('fort_sin:inplace:scalar',
     &      'fort_sin: inplace only support non-scalar arrays.')
          RETURN
        END IF
        IF (nlhs > 0) THEN
          plhs(1) = prhs(2)
        END IF
      ELSE
C       CREATE MATRIX FOR THE RETURN ARGUMENT.
        plhs(1) = mxCreateDoubleMatrix(M, N, 0)
        Y_PTR = mxGetPr(plhs(1))
      END IF
C
C
C     CALL THE COMPUTATIONAL ROUTINE.
      CALL COMPUTE(%VAL(Y_PTR), %VAL(X_PTR), M, N)
C
C
      RETURN
      END
C
C
C=======================================================================
C
C     COMPUTE.F
C
C=======================================================================
C
      SUBROUTINE COMPUTE(Y, X, M, N)
C
      IMPLICIT NONE
C
      mwSize, INTENT(IN)    :: M, N
      REAL*8, INTENT(IN)    :: X(M, N)
      REAL*8, INTENT(INOUT) :: Y(M, N)
C ----------------------------------------------------------------------
C
C
      Y = SIN(X)
C
      RETURN
      END
C
C ----------------------------------------------------------------------
C ----------------------------------------------------------------------
C
C
C

The compute routine is a Fortran routine.

So, the arguments are both arrays (often trivial, but still). In that case I do not see the usefulness or even correctness of %VAL(). That function is meant to transfer a value rather than the address where the value can be found, right? For arrays, even of size 1, there is no possibility to transfer the values in that way.
Unless I am completely mistaken and should simply not interfer :innocent:

Y_PTR and X_PTR are addresses, to arrays. %VAL would make COMPUTE operate on the underlying values, right?

At least that is what is happening, it has been working well for many years now :wink:

Oh, double redirection. Now I understand.

Oh, I missed that part too. When you say address, that means what is returned bu ‘loc’ or ‘c_loc’? If so, what about using c_f_pointer?

How would such a change look like?

In practice mwPointer is an integer*8 and is meant to contain an address.

What is unclear to is the status of the compute routine: is it a routine that you can modify, or do you have to use it “as is” ?

I was playing around with the c_f_pointer function, and got past some initial errors, but got this:

Error using mex
Undefined symbols for architecture arm64:
  "_c_f_pointer_", referenced from:
      _fsin_MP_mexfunction in fsin.o
      _fsin_MP_mexfunction in fsin.o
  "_mexfunction_", referenced from:
      <initial-undefines>
ld: symbol(s) not found for architecture arm64
clang: error: linker command failed with exit code 1 (use -v to see invocation) 

That seems strange?

Ask NAG support, “why keep a dog and bark yourself?”

It can be freely modified.

I am just testing this using a trial license, not sure if support is included.

It used to be, when I worked there.

Without modifying the compute routine, I would try adding an interface block in the calling routine (that is MEXFUNCTION):

interface
   subroutine compute(x,y,m,n)
      mwSize, intent(in) :: m, n
      mwPointer, value :: x, y
   end subroutine
end interface

EDIT: looking more closely at your previous posts, in the present case the VALUE attribute must NOT be added in the compute routine itself, it just has to be used in an interface block.

EDIT2: and, the compute routine must be taken out of the module, otherwise the compiler will always report argument mismatchs

1 Like

Read the documentation provided in the compiler.pdf in your NAG installation. You probably need page 125, 70.4 “BIND(C) procedures”.

Also, at https://support.nag.com/nagware/np/r72_doc/compiler.pdf

This is with some changes:

#include "fintrf.h"
C=======================================================================
C
C=======================================================================
      SUBROUTINE MEXFUNCTION(nlhs, plhs, nrhs, prhs)
C
      IMPLICIT NONE
C
      mwPointer :: plhs(*), prhs(*)
      INTEGER*4 :: nlhs, nrhs
C
      mwPointer :: mxGetPr
      mwPointer :: mxGetM
      mwPointer :: mxGetN
C
      mwPointer :: X_PTR, Y_PTR
      mwSize    :: M, N

      interface
        subroutine compute(x,y,m,n)
          mwSize, intent(in) :: m, n
          mwPointer, VALUE :: x, y
        end subroutine
      end interface
C
C-----------------------------------------------------------------------
C
C     GET THE SIZE OF THE INPUT X.
      M = mxGetM(prhs(1))
      N = mxGetN(prhs(1))
C
C     GET POINTERS FROM THE INPUT ARGUMENTS.
      X_PTR = mxGetPr(prhs(1))
      Y_PTR = mxGetPr(prhs(2))
C
C     CALL THE COMPUTATIONAL ROUTINE.
      CALL COMPUTE(Y_PTR, X_PTR, M, N)
C
C
      RETURN
      END
C
C
C=======================================================================
C
      SUBROUTINE COMPUTE(Y, X, M, N)
C
      IMPLICIT NONE
C
      mwSize, INTENT(IN) :: M, N
      REAL*8             :: X(M,N)
      REAL*8             :: Y(M,N)
C ----------------------------------------------------------------------
C
      Y = SIN(X)
C
      RETURN
      END
C
C ----------------------------------------------------------------------
C ----------------------------------------------------------------------
C
C
C

I get this kind of error for both arguments:

Inconsistent INTERFACE block for procedure COMPUTE from MEXFUNCTION
       Argument Y (no. 1) should not have the VALUE attribute