Search code examples
fortrangfortrangeneric-programmingallocatable-array

Why does this Fortran module interface give different results depending on how many of its functions are used?


I have written a module that contains a interface called 'push' that pushes values onto allocatable arrays. I want it to have generic behavior so that I can add a new function for a given type to the 'push' interface as needed. The problem is that as the amount of functions for a given interface grows, so does the strange behavior of the push interface.

Code for the module (push_array.f90):

module push_array
  implicit none
  ! usage:
  ! array = push(array,val)
  interface push
     module procedure push_scalar_int_onto_rank1_int
     module procedure push_scalar_int2_onto_rank1_int2
     module procedure push_rank1_int_onto_rank2_int
     module procedure push_rank1_real8_onto_rank2_real8
  end interface push

contains
  function push_scalar_int_onto_rank1_int (array,val) result (new_array)
    integer,intent(in),allocatable :: array(:)
    integer,intent(in) :: val
    integer,allocatable :: new_array(:)
    integer :: length
    if (allocated(array)) then
       length = size(array) + 1
    else
       length = 1
    end if
    allocate(new_array(size(array) + 1))
    if (allocated(array)) new_array(:) = array(:)
    new_array(length) = val
    return
  end function push_scalar_int_onto_rank1_int

  function push_scalar_int2_onto_rank1_int2 (array,val) result (new_array)
    integer(2),intent(in),allocatable :: array(:)
    integer(2),intent(in) :: val
    integer(2),allocatable :: new_array(:)
    integer :: length
    if (allocated(array)) then
       length = size(array) + 1
    else
       length = 1
    end if
    allocate(new_array(size(array) + 1))
    if (allocated(array)) new_array(:) = array(:)
    new_array(length) = val
    return
  end function push_scalar_int2_onto_rank1_int2

  function push_rank1_int_onto_rank2_int (array,val) result (new_array)
    integer,intent(in),allocatable :: array(:,:)
    integer,intent(in) :: val(:)
    integer,allocatable :: new_array(:,:)
    integer :: length
    if (allocated(array)) then
       length = size(array,2) + 1
    else
       length = 1
    end if
    allocate(new_array(1:size(val),length))
    if (allocated(array)) new_array(1:size(val),:) = array(1:size(val),:)
    new_array(1:size(val),length) = val
    return
  end function push_rank1_int_onto_rank2_int

    function push_rank1_real8_onto_rank2_real8 (array,val) result (new_array)
    real(8),intent(in),allocatable :: array(:,:)
    real(8),intent(in) :: val(:)
    real(8),allocatable :: new_array(:,:)
    integer :: length
    if (allocated(array)) then
       length = size(array,2) + 1
    else
       length = 1
    end if
    allocate(new_array(1:size(val),length))
    if (allocated(array)) new_array(1:size(val),:) = array(1:size(val),:)
    new_array(1:size(val),length) = val
    return
  end function push_rank1_real8_onto_rank2_real8

end module push_array

Test code (test_push_array.f90):

program main
  use push_array, only: push
  implicit none
  integer,allocatable :: a(:)
  integer(2),allocatable :: b(:)
  integer,allocatable :: c(:,:)
  real(8),allocatable :: d(:,:)
  integer :: xp(3)
  real(8) :: xp8(3)
  integer :: i
  integer(2) :: j
  ! test that a scalar integer can be pushed onto a rank1 integer array
  do i=1,100
     a = push(a,i)
  end do
  print *, a(1),a(100)

  ! test that a scalar integer(2) can be pushed onto a rank1 integer(2) array
  do j=1,100
     b = push(b,j)
  end do
  print *, b(1),b(100)

  ! test that a rank1 integer can be pushed onto a rank2 integer
  do i=1,100
     xp = [i,i+1,i+2]
     c = push(c,xp)
  end do
  print *, c(1:3,1),c(1:3,100)

  ! test that a rank1 real(8) can be pushed onto a rank2 real(8)
  do i=1,100
     xp8 = [i + 0.001,i + 0.002, i + 0.003]
     d = push(d,xp8)
  end do
  print *, d(:,1),d(:,100)

end program main

make output to show compiler flags:

$ make
gfortran -g -O2 -c push_array.f90
gfortran -g -O2 -o main test_push_array.f90 push_array.o

My compiler version:

$ gfortran --version
GNU Fortran (GCC) 4.8.2
Copyright (C) 2013 Free Software Foundation, Inc.

My system:

$ uname -a
Darwin darthan 12.5.0 Darwin Kernel Version 12.5.0: Sun Sep 29 13:33:47 PDT 2013; root:xnu-2050.48.12~1/RELEASE_X86_64 x86_64

If I run the test code with as given, it goes into an infinite loop and my system memory is completely exhausted. I tried to trace the test case in gdb by setting breakpoint where I push i onto a in the first loop,but gdb is unable to step into the module function.

If I comment just the first test loop where i is pushed onto a, here are the results:

$ ./main
      1    100
           1           2           3         100         101         102
   1.0010000467300415        1.0019999742507935        1.0030000209808350        100.00099945068359        100.00199890136719        100.00299835205078     

These would be expected.

If I comment out just the second loop where I push j onto b, here are the results:

$ ./main
           1         100
           1           2           3         100         101         102
   1.0010000467300415        1.0019999742507935        1.0030000209808350        100.00099945068359        100.00199890136719        100.00299835205078     

Once again, as expected.

Things start getting strange when I comment out just the third loop where I push xp onto c:

$ ./main
           1           0
      1      0
   1.0010000467300415        1.0019999742507935        1.0030000209808350        100.00099945068359        100.00199890136719        100.00299835205078     

The pattern continues when I comment out just the fourth loop where I push xp8 onto d:

$ ./main
           1           0
      1      0
           1           2           3         100         101         102

My questions:

  1. Why does the main test program go into a infinite loop when I try to use all four functions defined in the push interface in the same program?

  2. In the case where I comment out the third and fourth loops , why do the results for a(100) and b(100) both equal to 0?

Any feedback would be appreciated...thanks!

Edit:

The two functions that needed to be changed are given below

  function push_scalar_int_onto_rank1_int (array,val) result (new_array)
    integer,intent(in),allocatable :: array(:)
    integer,intent(in) :: val
    integer,allocatable :: new_array(:)
    integer :: length
    if (allocated(array)) then
       length = size(array) + 1
    else
       length = 1
    end if
    allocate(new_array(length)) ! changed
    if (allocated(array)) new_array(:) = array(:)
    new_array(length) = val
    return
  end function push_scalar_int_onto_rank1_int

  function push_scalar_int2_onto_rank1_int2 (array,val) result (new_array)
    integer(2),intent(in),allocatable :: array(:)
    integer(2),intent(in) :: val
    integer(2),allocatable :: new_array(:)
    integer :: length
    if (allocated(array)) then
       length = size(array) + 1
    else
       length = 1
    end if
    allocate(new_array(length)) ! changed
    if (allocated(array)) new_array(:) = array(:)
    new_array(length) = val
    return
  end function push_scalar_int2_onto_rank1_int2

Solution

  • You allocate statement in some of the function bodies references the size of the array argument. If the array argument is not allocated, that reference is invalid.

    Earlier in the procedure you test for allocation status and set a variable named length - perhaps you meant to use that.

    (For clarity - perhaps look at the allocate statement in the push_scalar_int_onto_rank1_int function.)