With these compiler options, how do I prevent this error and maintain the logic in the program?
-g -Wall -Werror -fmax-errors=1 -fcheck=all
SUBROUTINE TESTING (cars)
CHARACTER cars*(*)
print *,"CARS=", cars(1),cars(2),cars(3)
end
Program TEST
Character test1 * 10
Character test2 * 30
COMMON /ABC/test1(10)
COMMON /DEF/test2(30)
test1(1)= 'A'
test1(2)= 'B'
test1(3)= 'C'
CALL TESTING (test1)
test2(1)= 'X'
test2(2)= 'Y'
test2(3)= 'Z'
CALL TESTING (test2)
End Program TEST
Error Message:
13 | CALL TESTING (test1)
| 1
Error: Rank mismatch in argument ‘cars’ at (1) (scalar and rank-1) [-Werror=argument-mismatch]
f951: all warnings being treated as errors
module testing_mod
implicit none
character(len=10) :: test1(10)
character(len=30) :: test2(30)
contains
subroutine testing_sub (cars)
character(*) :: cars(:)
print *,"CARS=", cars(1),cars(2),cars(3)
end subroutine testing_sub
end module testing_mod
program test
use testing_mod
test1(1)= "A"
test1(2)= "B"
test1(3)= "C"
call testing_sub(test1)
test2(1)= "X"
test2(2)= "Y"
test2(3)= "Z"
call testing_sub(test2)
end program test
``
gfortran -g -Wall -Werror -fmax-errors=1 -fcheck=all rank.f90 -o rank
./rank
CARS=A B C
CARS=X Y Z
Maybe it is worth explaining the problem with original source, apparently Fortran 77 standard, as there are several errors in it.
CHARACTER cars*(*) tells the compiler that the dummy argument cars will be an object of type assumed length character scalar, not an array! It is F77 way of modern CHARACTER(LEN=*). Furthermore, the nature of this object is deduced by the compiler only when it finds it in context, here the context is print *,"CARS=",cars(1).... As cars is a scalar, not an array, cars(1) is interpreted as a function call, thus making the cars a dummy procedure!
In the main program, test1 and test2 are defined as arrays (1-dimensional, a.k.a. rank-1) of character elements having the length of 10 and 30, respectively. This is why you get Rank mismatch.. (scalar and rank-1) at CALL TESTING() statement.
So, to keep the old format, you’d have to change the dummy declaration to CHARACTER*(*) cars(*)
to make it an array of assumed length character elements
To get convinced about the point 1 above regarding the dummy procedure, change (in the original code!) the test1 and test2 in CALL TESTING() to any scalar character value, say "abc" and "def" and compile. You’ll get something like: Error: Expected a procedure for argument 'cars'
Surely @alozada’s solution is much better, converted to modern Fortran.
As it is now, without the magical *(*) , cars dummy argument is an array of len=1 character elements. And you are sending arrays of len=10 or len=30 elements