21

The following code is returning a Segmentation Fault because the allocatable array I am trying to pass is not being properly recognized (size returns 1, when it should be 3). In this page (http://www.eng-tips.com/viewthread.cfm?qid=170599) a similar example seems to indicate that it should work fine in F95; my code file has a .F90 extension, but I tried changing it to F95, and I am using gfortran to compile.

My guess is that the problem should be in the way I am passing the allocatable array to the subroutine; What am I doing wrong?

!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%!
 PROGRAM test
!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%!
 IMPLICIT NONE
 DOUBLE PRECISION,ALLOCATABLE :: Array(:,:)
 INTEGER                      :: iii,jjj

 ALLOCATE(Array(3,3))
 DO iii=1,3
 DO jjj=1,3
    Array(iii,jjj)=iii+jjj
    PRINT*,Array(iii,jjj)
 ENDDO
 ENDDO
 CALL Subtest(Array)

 END PROGRAM
!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%!
 SUBROUTINE Subtest(Array)
 DOUBLE PRECISION,ALLOCATABLE,INTENT(IN) :: Array(:,:)
 INTEGER                                 :: iii,jjj

 PRINT*,SIZE(Array,1),SIZE(Array,2)
 DO iii=1,SIZE(Array,1)
 DO jjj=1,SIZE(Array,2)
    PRINT*,Array(iii,jjj)
 ENDDO
 ENDDO

 END SUBROUTINE
!%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%!
Nordico
  • 1,226
  • 2
  • 15
  • 31
  • 1
    Note that allocatable dummy arguments are actually a (widely supported - including gfortran for some years now) Fortran 2003 feature. – IanH Oct 24 '12 at 23:28

3 Answers3

33

If a procedure has a dummy argument that is an allocatable, then an explicit interface is required in any calling scope.

(There are numerous things that require an explicit interface, an allocatable dummy is but one.)

You can provide that explicit interface yourself by putting an interface block for your subroutine inside the main program. An alternative and far, far, far better option is to put the subroutine inside a module and then USE that module in the main program - the explicit interface is then automatically created. There is an example of this on the eng-tips site that you provided a link to - see the post by xwb.

Note that it only makes sense for a dummy argument to have the allocatable attribute if you are going to do something related to its allocation status - query its status, reallocate it, deallocate it, etc.

IanH
  • 21,026
  • 2
  • 37
  • 59
  • Thanks, this was my problem. I knew that some functions (don't remember the name they had, but I think they were the ones that changed the input parameters) needed explicit interfaces, but didn't know allocation was the same. And yes, the code was made for the purpose of debugging my real code. – Nordico Oct 26 '12 at 19:59
9

Please also note that your allocatable dummy argument array is declared with intent(in), which means its allocation status will be that of the associated actual argument (and it may not be changed during the procedure). The actual argument passed to your subroutine may be unallocated and therefore illegal to reference, even with an explicit interface. The compiler will not know this and the behaviour of inquiries like size is undefined in such cases.

Hence, you first have to check the allocation status of array with allocated(array) before referencing its contents. I would further suggest to implement loops over the full array with lbound and ubound, since in general you can't be sure about array's bounds:

subroutine subtest(array)
  double precision, allocatable, intent(in) :: array(:,:)
  integer                                   :: iii, jjj

  if(allocated(array)) then
    print*, size(array, 1), size(array, 2)
    do iii = lbound(array, 1), ubound(array, 1)
      do jjj = lbound(array, 2), ubound(array, 2)
        print*, array(iii,jjj)
      enddo
    enddo
  endif  
end subroutine
sigma
  • 2,758
  • 1
  • 14
  • 18
  • Note: Added this as a new answer because I can't comment on others yet. It's more of an extension to IanH's answer that I think is important, since this subtlety is also missed in xwb's post at eng-tips.com. I didn't want to barge in with a big edit; feel free to merge this into one answer though. – sigma Oct 25 '12 at 16:41
  • ubound would seem to to have the same effect as Size; what is the difference? And the use of lbound is in case an array starts with index higher than 1? can that happen? – Nordico Oct 26 '12 at 19:51
  • 3
    `size` gives the total number of elements of an array (without a dim argument) or the number along any dimension (with a dim argument). You may allocate array with bounds `(-2:0, -2:0)` and the size will still be 3 along each dimension, but `array(1:3, 1:3)` is undefined. This is in contrast to a non-allocatable dummy array with assumed shape, where the lower bound is indeed assumed to be 1 if not specified. – sigma Oct 26 '12 at 21:59
2

This is a simple example that uses allocatable dummy arguments with a module.

module arrayMod   
  real,dimension(:,:),allocatable :: theArray    
end module arrayMod

program test
   use arrayMod
   implicit none

   interface
      subroutine arraySub
      end subroutine arraySub
   end interface

   write(*,*) allocated(theArray)
   call arraySub
   write(*,*) allocated(theArray) 
end program test

subroutine arraySub
   use arrayMod

   write(*,*) 'Inside arraySub()'
   allocate(theArray(3,2))
end subroutine arraySub
GPSmaster
  • 844
  • 3
  • 15
  • 31