next up previous 252
Next: Pointers
Up: Converting Between FORTRAN and C Strings
Previous: Handling Byte Strings (HDS Locators)


Using Dynamic FORTRAN Character Strings

The DECLARE_CHARACTER macro used in an earlier example assumes that the length of the required FORTRAN character string is a constant, known at compile time. This is not always the case - for example, the character argument to be passed to the FORTRAN subroutine may be derived from an argument of the calling C function as in the case of a C wrap-around for a FORTRAN subroutine. To cater for this situation, macros are provided which will allocate and free space for the FORTRAN character string at run time. They make use of the CNF functions cnfCref and cnfFreef.

The following example illustrates their use for both input and output of strings from a FORTRAN subroutine which takes a given string, modifies it and returns the result.

Example - Dynamic CHARACTER Arguments.

C main program

void strStrip( char *in, char *out, int maxout );

main(){
char in[20]="Hello  there  !";
char out[20];

printf( "Input string is: %s\n", in );
strStrip( in, out, 20 );
printf( "Output string is: %s.\n", out );
}
C wrap-around for a FORTRAN subroutine
/* strStrip - A C wrap-around for FORTRAN subroutine STR_STRIP */
#include "f77.h"

extern F77_SUBROUTINE(str_strip)
  ( CHARACTER(fin), CHARACTER(fout) TRAIL(fin) TRAIL(fout) );

void strStrip( char *in, char *out, int maxout ){
DECLARE_CHARACTER_DYN(fin);
DECLARE_CHARACTER_DYN(fout);

F77_CREATE_CHARACTER(fin,strlen(in));
F77_CREATE_CHARACTER(fout,maxout-1);

cnfExprt( in, fin, fin_length );

F77_CALL(str_strip)
   ( CHARACTER_ARG(fin), CHARACTER_ARG(fout)
     TRAIL_ARG(fin) TRAIL_ARG(fout) );

cnfImprt( fout, fout_length, out );

F77_FREE_CHARACTER(fin);
F77_FREE_CHARACTER(fout);
}

which is a C wrapper for the FORTRAN subroutine:

      SUBROUTINE STR_STRIP( FIN, FOUT )
* Remove multiple spaces from a string
      IMPLICIT NONE
      INTEGER I, J
      CHARACTER*(*) FIN
      CHARACTER*(*) FOUT
      
      FOUT = FIN(1:1)
      I = 2
      J = 1
      
      DOWHILE ( I .LE. LEN(FIN) )
         IF ( FIN(I:I) .NE. ' ' ) THEN
            J = J + 1
            FOUT(J:J) = FIN(I:I)
         ELSE IF ( FOUT(J:J) .NE. ' ' )
            J = J + 1
            FOUT(J:J) = FIN(I:I)
         END IF

         I = I + 1

      ENDDO

      END
Here, DECLARE_CHARACTER_DYN is used in place of DECLARE_CHARACTER. It declares pointers rather than allocating space for the FORTRAN character strings to be passed to the FORTRAN subroutine. A variable to hold the string length is also declared.

The F77_CREATE_CHARACTER expands to executable statements which allocate space and set the pointers and string length. The F77_FREE_CHARACTER macro expands to executable statements which free the previously allocated space.



next up previous 252
Next: Pointers
Up: Converting Between FORTRAN and C Strings
Previous: Handling Byte Strings (HDS Locators)

CNF and F77 Mixed Language Programming -- FORTRAN and C
Starlink User Note 209
P.M. Allan
A.J. Chipperfield
R.F. Warren-Smith
19 January 2000
E-mail:ussc@star.rl.ac.uk