HELPLIB.HLB  —  FORTRAN  Intrinsic Procedures, IARGPTR
  IARGPTR ()

  Class:  Inquiry function - Specific

  Returns a pointer to the actual argument list for the current
  routine.  IARGPTR takes no arguments and returns an INTEGER*8
  address of the calling-standard defined "argument block".

  The first element in the array contains the argument count;
  subsequent elements contain the INTEGER(KIND=8) address of the
  actual arguments.

  Formal (dummy) arguments which can be omitted must be declared
  VOLATILE.

  The following example shows the IARGPTR intrinsic:

  C      Test IARGPTR intrinsic function.
         EXTERNAL TEST_ARGPTR
         INTEGER*4 X,Y,Z,FOO
         X = 10
         Y = 20
         Z = 100
         FOO = 4

         PRINT 80, %LOC(X), %LOC(Y), %LOC(Z), %LOC(FOO)
  80     FORMAT (' Argument addresses: ',4(1X, Z16))
         CALL TEST_ARGPTR (4, X, Y, Z, FOO)
         END

         OPTIONS /EXTEND_SOURCE
         SUBROUTINE TEST_ARGPTR (N_ARGS)
         POINTER (II, I_ARGN)
         INTEGER*8 I_ARGN
         POINTER (I_PTR, I_VAL)
         INTEGER I_VAL

         II = IARGPTR()             ! Get address of arg block
         II = II + SIZEOF (II)      ! Get address of address of first arg

         DO I = 1, N_ARGS+1
          I_PTR = I_ARGN            ! Get address of actual from homed
                                    !   arg list
          print 90, I, I_PTR, I_VAL
  90      format ( ' Argument ',I2, ' address = ',Z16, ', contents = ',Z16)
          II = II + SIZEOF (II)  ! Get address of address of next arg
         END DO
         RETURN
         END
Close Help