Runtime error: Expected REAL for item 6 in formatted transfer, got CHARACTER

How do I change the first “write” statement (not the array definition) to make this work correctly?

main.c

#include <stdio.h>
#include <string.h>

void test2_(); /*float *q, int sugar, int firm, char *amt, float a, float b, float c);*/

int test1 (double z1, int firm, char *amt, double z2, double z3, double z4)
{
   float q;
   float  a, b, c;
   int sugar = 1; 

   q = (float) 1.0 + z1;
   a = (float) z2;
   b = (float) z3;
   c = (float) z4;
   
   printf ("test1: amt = %s\n",amt);
   test2_ (&q, &sugar, &firm, amt, &a, &b, &c);
   return 0;
}

int main ()
{
     double have1 = 100.0;
     int have2 = 1;
     char have3 [31] = "Rock And Roll";
     double have4 = 300.0;
     double have5 = 400.0;
     double have6 = 500.0;
     
     have3[31] = '\0';

     test1(have1, have2, have3, have4, have5, have6);
     return 0;
}

test.f:

       SUBROUTINE test2(Q, SUGAR, FIRM, AMT, A, B, C)
       IMPLICIT NONE
       INTEGER SUGAR, FIRM
       REAL Q, A, B, C
       CHARACTER AMT(31)
       CHARACTER*10 MILK
 
       INTEGER WATER,RICE
       CHARACTER*1000 THESTRING

       if (FIRM.EQ.1) THEN
         WRITE(THESTRING,
     &'(I3,1X,F16.2,1X,I2,1X,A4,1X,A26,3(1X,F10.4),1X,I2)') 
     &WATER,Q,SUGAR,MILK,AMT,A,B,C,RICE
         write(*,*)'THESTRING is ---> ',THESTRING
       ENDIF
 
       RETURN
       END

Compilation and run:

  gfortran -c -g test.f -o test.o
  gcc -c -g main.c -o main.o -DLINUX -DSYSV -DNOHLA -g -Wall -Werror -fmax-errors=1
  gfortran -g test.o main.o -o main.exe -lgfortran -w  -u -g -fno-second-underscore $(M32_OR_64_BIT_FLAG) -Wall -Werror -fmax-errors=1 -fcheck=all -fPIC
  ./main.exe

Output:

test1: amt = Rock And Roll
At line 14 of file test.f
Fortran runtime error: Expected REAL for item 6 in formatted transfer, got CHARACTER
(I3,1X,F16.2,1X,I2,1X,A4,1X,A26,3(1X,F10.4),1X,I2)

Maybe you could provide a link (or repository) of the original program. IMO this could help to know the general problem.

:smile: . Well, besides that, the original code would work if you used an array subscript and changed the A26 field, which is for one variable to 26(A), which is for 26 single characters.

       SUBROUTINE test2(Q, SUGAR, FIRM, AMT, A, B, C)
       IMPLICIT NONE
       INTEGER SUGAR, FIRM
       REAL Q, A, B, C
       CHARACTER AMT(31)
       CHARACTER*10 MILK

       INTEGER WATER,RICE
       CHARACTER*1000 THESTRING
       water=0 ! undefined
       milk='chocolate' !undefined
       rice=10 ! undefined

       if (FIRM.EQ.1) THEN
         WRITE(THESTRING,
     &'(I3,1X,
     & F16.2,1X,
     & I2,1X,
     & A4,1X,
     & 26(A),
     & 3(1X,F10.4),1X,
     & I2)')
     &WATER,Q,SUGAR,MILK,AMT(:26),A,B,C,RICE
         write(*,*)'THESTRING is ---> ',THESTRING
       ENDIF

       RETURN
       END

When you changed AMT from a string to an array, you needed to supply 31 fields for 31 separate values. A31 means one variable is given a 31-character field. 31(A1) means give 31 values a one-character field. In your case you only want to print 26 of the values, so you would use 26 and change the write of the array AMT to AMT(:26).

If you put your value back to a string it would have worked; or you could have converted the array to a simple string. So you really did have a type mismatch, as the first element in the array was printed with the A26 field, and the second letter was printed with the F10.4 field.

The symptoms you describe in general hint that memory was smacked somewhere, and then behavior becomes very unpredictable. There are issues with a Fortran string and C that are long-standing, so it is not too surprising a character array worked and a character value did not. If you are going to pass a CHARACTER string you want to look into using the ISO_C_BINDING interface; and making that routine into a free-format F90+ procedure and so on, but I hope that explains why the compiler was giving you a CORRECT diagnostic.

You will also find your array ends with a bunch of null characters, not spaces. Passing strings can be tricky and non-portable directly hooking C and Fortran without using the standard-supported methods.

PS:
Note sure what system you are on, but if you have the cat(1) command it can show you the null characters, which can be problematic. They are the ^@ characters below:

  urbanjs@venus:~/github/fun/buguser$ ./main.exe
test1: amt = Rock And Roll
 THESTRING is --->   0           101.00  1 choc Rock And Roll   300.0000   400.0000   500.0000 10 
urbanjs@venus:~/github/fun/buguser$ ./main.exe|cat -vet
test1: amt = Rock And Roll$
 THESTRING is --->   0           101.00  1 choc Rock And Roll^@^@^@^@^@^@^@^@^@^@^@^@^@   300.0000   400.0000   500.0000 10 $

But in general, when doing custom C/Fortran interfaces remember C does not have the equivalent of a multi-character CHARACTER variable, so you have to know exactly how your compilers are handling it. Perhaps a character length is being passed invisibly, which is typical for Fortran; which might be smacking memory because your C interface does not have a matching field, just as one example.

PSS:
Anywhere else you are passing a CHARACTER value this way you are risking similar problems/corruption.