Error: Unexpected STATEMENT FUNCTION statement at (1)

I’ve taken a very small portion of code from my big program to show the error on the subject line. How do I get rid of this error if most of this code has to stay. DATAX has to be a two dimensional array.

I’m not allowed to use iso_c_binding!

      INTEGER FUNCTION GUESS(A,B,C,D)
      IMPLICIT NONE
      INTEGER A,B(*),C,D
      INTEGER DATAX,E
      INTEGER I,J
      write(*,*)'   '
      DATAX(I,J)=F(F(G+E)+I)+J
      GUESS=0
      RETURN
      END

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

void test_(char* z1, int leng);

int main ()
{
}

  gfortran -c -g work.f -o work.o -g -Wall -Werror -fmax-errors=1
  gcc -c -g main.c -o main.o 
  gfortran -g main.o work.o main.exe -Wall -Werror -fmax-errors=1
      DATAX(I,J)=F(F(G+E)+I)+J                                          
                                                                        1
Error: Unexpected STATEMENT FUNCTION statement at (1)
Fatal Error: Error count reached limit of 1.
1 Like

I think your entire program should be compiled with -std=legacy.

1 Like

It appears DATAX is intended to be a rank 2 array, but it is declared as an integer scalar. You need to modify the declaration of DATAX to include bounds. I.e.

INTEGER DATAX(I,J), E
1 Like

Move the statement function data(i,j) = ... above the write(*,*) statement. I’m assuming the write is a remnant of a poor man’s debugging workflow. For more background, check the Oracle documentation on statement functions. Since these are really function-like definitions, they belong in the specification section, before any executable statements like write.

Btw, statement functions have been marked as obsolescent for a while. See Questions about statement functions - #6 by msz59

2 Likes

DATAX cannot be declared an array with bounds I,J if I,J are local variables in the function. Its shape must be defined either by a constant compile-time expression or by expression involving dummy arguments (I assume there are no COMMON blocks in teh code

1 Like

Here is an example:

module m
implicit none
contains
function sum_mat(n1,n2,x) result(xsum)
integer, intent(in) :: n1, n2
real   , intent(in) :: x(n1,n2)
real                :: xsum
xsum = sum(x)
end function sum_mat
end module m

program main
use m, only: sum_mat
implicit none
integer, parameter :: n1 = 2, n2 = 3
real :: x(n1,n2)
call random_number(x)
print*,sum(x),sum_mat(n1,n2,x) ! will give same result
end program main

Ok, so is datax supposed to be an array or is it supposed to be a statement function? How is it used later in the code? Because if it is supposed to be a statement function, then @ivanpribec is correct, it must appear before any executable statements. If it’s supposed to be an array, then you need to figure out what the actual dimensions are supposed to be. It must be at least as big as i and j ever get if that’s the case. Without more of the actual code, I’m afraid it’s near impossible to tell which is the case.

this was in OP first message, so NOT a statement function

I’m actually leaning towards DATAX is supposed to be a statement function. In that case, I and J are it’s arguments, not used to index into an array. If DATAX is passed as an argument, is the whole thing passed, or is it used like DATAX(1,2)? The declaration INTEGER DATAX can also mean that DATAX is a function that returns an INTEGER, and so the statement function actually makes sense.

1 Like

Passed? Where? No trace of DATAX being a dummy argument. It is a total mess.

1 Like
DATAX(I,J)=F(F(G+E)+I)+J

is F an external function. If so, try declaring it to be external before the write statement.

external F

DATAX(I,J)=F(F(G+E)+I)+J

I notice that G seems to be not declared

Then it is a statement function, and DATAX(1,2) calls it with arguments (1, 2) and passes the result as the actual argument.

That act, by itself, is the major source of error as far as this post is concerned. By taking out essential parts and leaving in inconsequential parts, you have presented code fragments that make no sense.

By presenting different fragments to the compiler, you may cause it to emit a variety of error messages, but most of those messages may have no bearing on the original code.

Consider the C main program that you showed. It has no connection at all to the Fortran subroutine. That C fragment declares an external function called test_, but you did not show the invocation of that function, nor does that name ever occur in the Fortran source lines that you showed.

Well, in that case, the code that you did not show could be something similar to

program logical
character*4 data
data data/'(A)'/
write(data,'(A)')'Data'
print *,data
end program

and this thread can become arbitrarily long! :weary: