I have a problem using ALLOCATE and mixing /opt with /check, where I get an integer overflow error using FTN95 Ver 7.1, although this problem has been around for years. my main program is compiled with /opt ( I think /debug also) my subroutine I am checking is compiled with /check In general, I am using /check to check the subroutine argument lists. The following is a cut down example; hopefully with no errors!
! test_call.f90
! Program to produce integer overflow error
!
real*8, allocatable, dimension(:,:) :: EPROP
integer*4 :: Num_Mat = 5
integer*4 num, stat
!
ALLOCATE ( EPROP(16,NUM_MAT), stat=stat )
!
CALL B2MAT_read (NUM_MAT, EPROP, num)
!
end
LOGICAL FUNCTION EQUAL_DUMMY (VARIABLE)
!
real*8 :: DUMMY = -.99898d00 ! special coordinate for undefined coordinates
!
REAL*8 VARIABLE
!
equal_dummy = ( variable == DUMMY )
RETURN
END FUNCTION EQUAL_DUMMY
SUBROUTINE SET_DUMMY (VARIABLE)
!
real*8 :: DUMMY = -.99898d00 ! special coordinate for undefined coordinates
!
REAL*8 VARIABLE
!
variable = DUMMY
RETURN
END SUBROUTINE SET_DUMMY
! test_called.f90
SUBROUTINE B2MAT_read (NUM_MAT, EPROP, num)
!
INTEGER*4 NUM_MAT, num
REAL*8 EPROP(16,*)
!
INTEGER*4 I
LOGICAL equal_dummy
EXTERNAL equal_dummy
!
CALL material_read (2, NUM_MAT, EPROP, num)
write (*,*) 'material_read <',num_mat,' >',num
!
DO I = 1,NUM_MAT
IF ( equal_dummy (EPROP(1,I)) ) cycle
EPROP(6,I) = 0.5*EPROP(1,I)/(1.+EPROP(2,I)) ! PR > G
END DO
!
RETURN
!
END SUBROUTINE B2MAT_read
SUBROUTINE material_read (NTYPE, NUM_MAT, EPROP, num)
!
INTEGER*4 NTYPE, NUM_MAT, num
REAL*8 EPROP(16,*)
INTEGER*4 I
!
DO I = 1,NUM_MAT
EPROP(:,I) = 0
call set_dummy (EPROP(1,I))
END DO
num = i
!
RETURN
!
END SUBROUTINE material_read
ftn95 test_call /opt
ftn95 test_called /check
slink test_call.obj test_called.obj
test_call
Running this batch file produces the error The error is when accessing the logical function.
This logical function has a history of being a patch to remove warnings about testing (real.eq.real) but is now crashing with tests on allocated arrays.
I think the problem relates to /check having trouble with the information about the array EPROP, which is being provided from the call. If the main is compiled with /check all is ok, however /opt, /debug or no option all fail. I hope this is a good small example of a problem that has annoyed me for years. This problem limits the usability of /check, especially when applying selective use of /check in a larger program.
John