Silverfrost Forums

Welcome to our forums

Problems with code when internal subroutines are present

29 Sep 2017 3:00 (Edited: 2 Oct 2017 6:57) #20332

I am observing a strange behavior using allocatable arrays in the presence of internal subroutines.

Consider the following program:

program main
    implicit none
    integer*4 :: n = 5
    real*8, allocatable, dimension(:,:) :: array

    allocate(array(6,n))
end program

I compiled it with ftn95 /full_debug main.f90 /checkmate /link and started it using the debugger sdbg main.exe

The program simply allocates an array(6,5), as shown by the debugger in the 'Vars' window. There, the exact output is: ARRAY = REAL*8 (6, 5)

Adding /64 yields the same result.

So far, so good.

Now I simply add an empty internal subroutine (for completeness I will provide the whole code again):

program main
    implicit none
    integer*4 :: n = 5
    real*8, allocatable, dimension(:,:) :: array

    allocate(array(6,n))
contains
    subroutine subsub
    end subroutine
end program

Using the same compiler options in 32 bit and examining with sdbg still yields the same output for the allocated array. However, if I compile the second code with /64, suddenly the array bounds are complete nonsense. In my particular case, the output was

ARRAY = REAL*8 (0:21844080, 20752:20757)

but I expect these values to vary (these bounds are definitely trash).

Interestingly, I was not able to produce an access violation in this small example and even the lbound/ubound and size intrinsic functions seem to work fine (despite the debugger output...). Admittedly, I did not try too hard either. By the way, checkmate does not complain at all (is it yet implemented in 64 bit??).

However I think that this might be some sort of compiler bug since one of our applications is crashing with spurious out-of-bounds errors/access violations when compiled with 64 bits and whenever internal subroutines are being used, while it did work fine in 32 bit. Actually these crashes along with this problem lead to the idea of examining the behavior of ALLOCATE in presence of internal subroutines.

Thanks for your help! Have a nice weekend! 😃

30 Sep 2017 2:01 #20334

Your program does nothing, apart from the allocate. Put a statement after the allocate, so you have a point after where sdbg can review what has happened, such as:

program main 
    implicit none 
    integer*4 :: n = 5 
    real*8, allocatable, dimension(:,:) :: array 

    allocate(array(6,n)) 
    array = 1

contains 
    subroutine subsub 
    end subroutine 
end program 

I would at least enhance the program to check the allocate and give subsub an address to work on.

program main 
    implicit none 
    integer*4 :: n = 5 
    integer*4 :: stat
    real*8, allocatable, dimension(:,:) :: array 

    allocate(array(6,n),stat=stat) 
    write (*,*) 'allocate array : stat=',stat
    array = 1

contains 
    subroutine subsub 
     write (*,*) 'in subsub'
     return
    end subroutine 
end program 

If the error is SDBG64 can't handle a program that does nothing, I can cope with that.

30 Sep 2017 2:26 #20335

Ok, I tried my revised code version with sdbg64 Ver 8.10 (12/2/2017) and it gave incorrect array dimensions, when using F7 to step through the program. I should install some of the updates since Feb 17 and see what happens. If compiled with /debug /64 /link, the following program runs in sdbg64 reporting the correct dimensions with the write statements, but displays the incorrect dimensions in the 'Variables:' window.

program main 
    implicit none 
    integer*4 :: n = 5 
    integer*4 :: stat
    real*8, allocatable, dimension(:,:) :: array 

    allocate(array(6,n),stat=stat) 
    write (*,*) 'allocate array : stat=',stat, ' : size=',size(array)
    write (*,*) 'lbound =',lbound(array)
    write (*,*) 'ubound =',ubound(array)
    array = 1

contains 
    subroutine subsub 
     write (*,*) 'in subsub'
     return
    end subroutine 
end program 

I have updated sdbg64.exe to ver 8.10.11 (Sat Sep 16, 2017)and

  1. reports correct dimensions with write statements
  2. it still provides incorrect array dimensions in 'Variables:' window
  3. it now closes the screen when selecting EXIT (Ver 8.10.9 would not close)
1 Oct 2017 3:08 #20344

If you remove subsub it debugs okay.

I'll take a look at it.

2 Oct 2017 6:42 (Edited: 2 Oct 2017 7:02) #20348

John, I wanted to give a minimal example and in fact, the code that I posted resulted from subsequently removing statements from a more complex code. I removed the bits that didn't seem to have any effect on the outcome. But apparently you have also observed that same strange behavior.

While the issue might be related to sdbg (I am using the latest version as provided in the link from this discussion), still I observe that code containing internal subroutines starts to show weird behavior in 64bit while it worked fine for 32bit (no matter if built for release or debug). Let me give you a better (and far more critical) example for this. (Unfortunately I am not allowed to post the code in question here and anyway it would be too large to post the full contents). I think that the following snippet cleary shows the unusual behavior:

SUBROUTINE rb_restpos_g (mmb, c_trans, c_rot, iter, ierror, crash)
!...
integer(singI) ,INTENT(in)  :: mmb, c_trans,  c_rot
integer(singI) ,INTENT(out)  :: iter
integer(singI) ,INTENT(out)  :: ierror
logical, INTENT(out)  ::  crash

! ...

write (*,*) 'Before call: loc(mmb)=', loc(mmb)
CALL estimate (1)
! ...

CONTAINS

! ...

SUBROUTINE estimate (state)
    integer(singI), INTENT(in)  ::  state


   write (*,*) 'Within call: loc(mmb)=', loc(mmb)

   ! ...
END SUBROUTINE estimate
END SUBROUTINE rb_restpos_g

When I compile in 32bit (the application is a ClearWin+ application), the output is:

Before call:  loc(mmb)=        18794008
Within call:  loc(mmb)=        18794008

and the rest of the code works as expected. In 64 bit, the same code outputs:

Before call:  loc(mmb)=            16650768
Within call:  loc(mmb)=        128849018994

and the code fails with an access violation if I try to read mmb. This clearly shouldn't happen, or am I overseeing something?

2 Oct 2017 6:58 #20349

I changed the topic message to reflect that the problem is not only related to allocatable arrays.

Please login to reply.