Bug 20541

Summary: TR 15581: ALLOCATABLE components
Product: gcc Reporter: Jason Byrd <madbosun>
Component: fortranAssignee: eedelman
Status: RESOLVED FIXED    
Severity: enhancement CC: dir, erik.edelmann, fxcoudert, gcc-bugs, P.Schaffnit, sfilippone, tkoenig, tobias.burnus
Priority: P2 Keywords: rejects-valid
Version: 4.0.0   
Target Milestone: 4.2.0   
Host: Target:
Build: Known to work:
Known to fail: Last reconfirmed: 2005-12-30 19:43:48
Bug Depends on:    
Bug Blocks: 20585, 16136    
Attachments: For discussion, perusal and testing: a beta-release of the TR15581 patch
An unpolluted version of the beta-release patch
The latest version of the patch
Latest version
Updated patch
New version.
Updated patch
Latest patch
Patch + testcases for allocatable components
The latest version, incorporating all fixes so far.
Patch that fixes Salvatore's latest
A patch that fixes test_ab9.f90

Description Jason Byrd 2005-03-18 20:43:02 UTC
This line is a allocatable integer type declaration in a standard module

"
gfortran -ffree-form -O3 -c dvr.f90
 In file dvr.f90:8

    INTEGER(kind=4), ALLOCATABLE :: glmark(:)
                               1
Error: Attribute at (1) is not allowed in a TYPE definition
make: *** [dvr.mod] Error 1
"

And so the compiler exits on the error

The partial source for the module.

MODULE DVR
  implicit none
!  PRIVATE
  PUBLIC :: buildgrid, writegrid, creategrid1, creategrid2, ecscreategrid1,
ecscreategrid2

  TYPE dvrgrid
    INTEGER(kind=4) :: gln, nfe, cess, nnodes, nreal, ncomplex, gnn, fim, lim
    INTEGER(kind=4), ALLOCATABLE :: glmark(:)
    REAL(kind=8) :: phi
    REAL(kind=8), pointer :: fenodes(:), gnodes(:), rnodes(:), wr(:)
    COMPLEX(kind=8), pointer :: znodes(:), wz(:)
  END TYPE dvrgrid

!  INTERFACE buildgrid
!    MODULE PROCEDURE creategrid1, creategrid2, ecscreategrid1, ecscreategrid2
  END INTERFACE

  INTERFACE D1node
    MODULE PROCEDURE D1glnode, D1gennode
  END INTERFACE

CONTAINS

!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

END MODULE DVR
Comment 1 kargls 2005-03-18 22:08:57 UTC
Your code is illegal with respect to the Fortran 95 standard.  See section
4.4.1, page 38, of the (draft) standard, you'll find the following 

R426  component-attr-spec   is POINTER
                            or DIMENSION ( component-array-spec )

Note ALLOACTABLE is not listed above.

If you have Metcalf & Reid, Fortran 90/95 Explained, 2nd ed., you'll find on
page 107:

   If a variable-sized array component of a structure is required,
   unfortunately, an array pointer must be used (see Section 6.14).
   The prohibition on allocatable arrays here was made to keep the
   the feature simple, but this is now recognized as a mistake that
   will be corrected in Fortran 2000
  
Comment 2 Tobias Schlüter 2005-03-20 18:08:02 UTC
This only allowed after TR15581 which is unimplemented so far in gfortran.
Comment 3 Francois-Xavier Coudert 2005-04-22 12:42:25 UTC
This prevents compiling the common iso_varying_string module by Rich Townsend.
Comment 4 Tillmann Wegst 2005-07-29 08:21:48 UTC
I found that code containing allocatable fields in type statements compiles 
without complaints using "g95", so I was a bit perplex when moving to gfortran 
and getting the same error as reported here. 

Consulting Metcalf et al, "fortran 95/2003 explained", chap. 7.12, pages 149f., 
I did not find anything as to a conflict between attributes "allocatable" 
and "dimension". Has there been a change in the Fortran95 specs? 

If it is not a gfortran bug, what would be a work-around? Declare the variable 
as a pointer, allocate the array in a subroutine and then direct the pointer 
variable to it? That seems like a way out, though clumsy. 
Comment 5 Erik Edelmann 2005-09-27 15:21:30 UTC
Working on a patch.
Comment 6 Erik Edelmann 2005-09-29 19:48:28 UTC
(In reply to comment #5)
> Working on a patch.

Turned out to be much more work than I first thought.  I'll leave it for now.
Comment 7 Steven Bosscher 2006-03-12 19:53:36 UTC
Good luck Erik.
Comment 8 Thomas Koenig 2006-05-09 21:27:28 UTC
Eric,

when you work on this, watch out for the following test case:

PROGRAM MAIN
  TYPE foo
     INTEGER, DIMENSION(:), ALLOCATABLE :: array
  END TYPE foo

  type(foo),pointer,dimension(:) :: mol

  ALLOCATE (mol(1))
  ALLOCATE (mol(1)%array(5))
  ALLOCATE (mol(1)%array(5),stat=i)
  if (i == 0) call abort

END PROGRAM MAIN

This is the reverse (more or less) of PR 27470.
        Thomas
Comment 9 Paul Thomas 2006-07-12 14:20:53 UTC
Created attachment 11867 [details]
For discussion, perusal and testing: a beta-release of the TR15581 patch

This patch represents some months of work by Erik and myself.  It is still not complete and has at least one residual source of memory leakage (derived type constructors with function array-valued actuals). That withstanding, it does most of the memory management required by the standard, it does assignments correctly and handless allocatable components in contructors.  There is still a way to go before it is submittable but it's getting there!

What does it do?

(i) It runs most of the iso_varying_string testsuite (vst16.f95 fails in io, vst28.f95, vst30.f95 and vst31.f95 need modification to catch zero length strings).

(ii) This tests the basic functionality:

! { dg-do run}
! { dg-options "-O2 -fdump-tree-original" }
!
! Check some basic functionality of allocatable components, including that they
! are nullified when created and automatically deallocated when
! 1. A variable goes out of scope
! 2. INTENT(OUT) dummies
! 3. Function results
!
module alloc_m

    implicit none

    type :: alloc1
        real, allocatable :: x(:)
    end type alloc1

end module alloc_m


program alloc

    use alloc_m

    implicit none

    type :: alloc2
        type(alloc1), allocatable :: a1(:)
        integer, allocatable :: a2(:)
    end type alloc2

    type(alloc2) :: b
    integer :: i
    type(alloc2), allocatable :: c(:)

    if (allocated(b%a2) .OR. allocated(b%a1)) then
        write (0, *) 'main - 1'
        call abort()
    end if

    ! 3 calls to _gfortran_deallocate (INTENT(OUT) dummy)
    call allocate_alloc2(b)
    call check_alloc2(b)

    do i = 1, size(b%a1)
        ! 1 call to _gfortran_deallocate
        deallocate(b%a1(i)%x)
    end do

    ! 3 calls to _gfortran_deallocate (INTENT(OUT) dummy)
    call allocate_alloc2(b)

    call check_alloc2(return_alloc2())
    ! 3 calls to _gfortran_deallocate (function result)

    allocate(c(1))
    ! 3 calls to _gfortran_deallocate (INTENT(OUT) dummy)
    call allocate_alloc2(c(1))
    ! 4 calls to _gfortran_deallocate
    deallocate(c)

    ! 7 calls to _gfortran_deallocate (b (3) and c(4) goes aout of scope)

contains

    subroutine allocate_alloc2(b)
        type(alloc2), intent(out) :: b
        integer :: i

        if (allocated(b%a2) .OR. allocated(b%a1)) then
            write (0, *) 'allocate_alloc2 - 1'
            call abort()
        end if

        allocate (b%a2(3))
        b%a2 = [ 1, 2, 3 ]

        allocate (b%a1(3))

        do i = 1, 3
            if (allocated(b%a1(i)%x)) then
                write (0, *) 'allocate_alloc2 - 2', i
                call abort()
            end if
            allocate (b%a1(i)%x(3))
            b%a1(i)%x = i + [ 1.0, 2.0, 3.0 ]
        end do

    end subroutine allocate_alloc2


    type(alloc2) function return_alloc2() result(b)
        if (allocated(b%a2) .OR. allocated(b%a1)) then
            write (0, *) 'return_alloc2 - 1'
            call abort()
        end if

        allocate (b%a2(3))
        b%a2 = [ 1, 2, 3 ]

        allocate (b%a1(3))

        do i = 1, 3
            if (allocated(b%a1(i)%x)) then
                write (0, *) 'return_alloc2 - 2', i
                call abort()
            end if
            allocate (b%a1(i)%x(3))
            b%a1(i)%x = i + [ 1.0, 2.0, 3.0 ]
        end do
    end function return_alloc2


    subroutine check_alloc2(b)
        type(alloc2), intent(in) :: b

        if (.NOT.(allocated(b%a2) .AND. allocated(b%a1))) then
            write (0, *) 'check_alloc2 - 1'
            call abort()
        end if
        if (any(b%a2 /= [ 1, 2, 3 ])) then
            write (0, *) 'check_alloc2 - 2'
            call abort()
        end if
        do i = 1, 3
            if (.NOT.allocated(b%a1(i)%x)) then
                write (0, *) 'check_alloc2 - 3', i
                call abort()
            end if
            if (any(b%a1(i)%x /= i + [ 1.0, 2.0, 3.0 ])) then
                write (0, *) 'check_alloc2 - 4', i
                call abort()
            end if
        end do
    end subroutine check_alloc2

end program alloc
! { dg-final { scan-tree-dump-times "deallocate" 24 "original" } }
! { dg-final { cleanup-tree-dump "original" } }


(iii) The following tests constructors:
program
  type :: mytype
    integer, allocatable :: a(:, :)
  end type mytype
  type (mytype) :: x
  integer :: y(0:1, -1:0) = reshape ((/42, 99, 55, 77/), (/2,2/))
  x = mytype (y)
  call foo (x, y)
  x = mytype (reshape ((/42, 99, 55, 77/), (/2,2/)))
  call foo (x, reshape ((/42, 99, 55, 77/), (/2,2/)))
  x = mytype (bar (y))
  call foo (x, y**3)
contains
  subroutine foo (x, y)
    type(mytype) :: x
    integer y(:,:)
    if (any (x%a .ne. y)) call abort ()
  end subroutine foo
  function bar (x)
    integer, dimension(:,:) :: x
    integer, dimension(size(x, 1), size(x, 2)) :: bar
    bar = x**3
  end function bar
end program

(iv) Whilst this tests assignments:

  type :: ivs
    character(1), allocatable :: chars(:)
  end type ivs

  type(ivs) :: a, b
  type(ivs) :: x(3), y(3)
  
  allocate(a%chars(5))
  a%chars = (/"h","e","l","l","o"/)

! An intrinsic assignment must deallocate the l-value, copy across the
! array and null the descriptor data field of the r-value.
  b = a
  if (any (b%chars .ne. (/"h","e","l","l","o"/))) call abort ()
  if (allocated (a%chars) .neqv. .false.) call abort ()

! Scalar to array needs to copy the derived type, to its ultimate components,
! to each of the l-value elements and then to deallocate the r-value.  */
  x = b
  x(2)%chars = (/"g","'","d","a","y"/)
  if (any (x(1)%chars .ne. (/"h","e","l","l","o"/))) call abort ()
  if (any (x(2)%chars .ne. (/"g","'","d","a","y"/))) call abort ()
  if (allocated (b%chars) .neqv. .false.) call abort ()
  deallocate (x(1)%chars, x(2)%chars)

! Array intrinsic assignments are like their scalar counterpart and
! must deallocate each element of the l-value, copy across the
! arrays from the r-value elements and null the descriptor data field
! of the r-value elements.
  allocate(x(1)%chars(5), x(2)%chars(5), x(3)%chars(5))
  x(1)%chars = (/"h","e","l","l","o"/)
  x(2)%chars = (/"g","'","d","a","y"/)
  x(3)%chars = (/"g","o","d","a","g"/)
  y(2:1:-1) = x(1:2)
  if (allocated (x(1)%chars) .neqv. .false.) call abort ()
  if (allocated (x(2)%chars) .neqv. .false.) call abort ()
  if (allocated (x(3)%chars) .neqv. .true.) call abort ()
  if (allocated (y(1)%chars) .neqv. .true.) call abort ()
  if (allocated (y(2)%chars) .neqv. .true.) call abort ()
  if (allocated (y(3)%chars) .neqv. .false.) call abort ()
  if (any (y(1)%chars .ne. (/"g","'","d","a","y"/))) call abort ()
  if (any (y(2)%chars .ne. (/"h","e","l","l","o"/))) call abort ()
  if (any (x(3)%chars .ne. (/"g","o","d","a","g"/))) call abort ()

! In the case of an assignment where there is a dependency, so that a
! temporary is necessary, each element must be copied to its destination
! and the source element nullified.
  y(2:3) = y(1:2)
  if (allocated (y(1)%chars)) call abort ()
  if (any (y(2)%chars .ne. (/"g","'","d","a","y"/))) call abort ()
  if (any (y(3)%chars .ne. (/"h","e","l","l","o"/))) call abort ()

end
Comment 10 Paul Thomas 2006-07-12 14:23:55 UTC
Bother! Forget the last test - it is an old, incorrect version.  I will post the right one tonight.

Paul

Comment 11 Paul Thomas 2006-07-12 19:41:31 UTC
Created attachment 11871 [details]
An unpolluted version of the beta-release patch

I do apologise; the previous diff was relative to a development tree that had another patch with it.  The net result was that it undid the committed patch and caused regressions.  The new attachment includes the three test cases; it regtests on tonight's trunk.

Paul
Comment 12 Paul Thomas 2006-07-18 14:35:22 UTC
Created attachment 11910 [details]
The latest version of the patch

This patch is the last version that I will post until after I return from vacation.  As well as allocatable components, it fixes the two issues raised by Salvatore Filippone on the gfortran list.  It also includes a test version of move_alloc that runs the following correctly:

  integer, allocatable :: x(:), y(:), temp(:)
  character(4), allocatable :: a(:), b(:)
  allocate (x(2))
  allocate (a(2))

  x = (/42, 77/)

  print *, allocated(x), allocated(y)
  if (allocated (x)) print *, x
  call move_alloc (x, y)
  print *, allocated(x), allocated(y)
  if (allocated (y)) print *, y


  a = (/"abcd", "efgh"/)
  print *, allocated(a), allocated(b)
  if (allocated (a)) print *, a
  call move_alloc (a, b)
  print *, allocated(a), allocated(b)
  if (allocated (b)) print *, b

! Now one of the intended applications of move_alloc; resizing

  call move_alloc (to = temp, from = y)
  allocate (y(6))
  y(1:2) = temp
  y(3:) = 99
  print *, y
end


Paul
Comment 13 eedelman 2006-07-30 21:38:46 UTC
Created attachment 11975 [details]
Latest version

Fixed a bunch of problems, added some documentation, and moved MOVE_ALLOC to a file of it's own.
Comment 14 Jack Howarth 2006-08-06 22:47:00 UTC
The current patch doesn't seem to work any more. I get a compile error on the current gcc trunk svn
pull...

../../gcc-4.2-20060806/gcc/fortran/parse.c: In function 'parse_derived':
../../gcc-4.2-20060806/gcc/fortran/parse.c:1601: error: 'c' undeclared (first use in this function)
../../gcc-4.2-20060806/gcc/fortran/parse.c:1601: error: (Each undeclared identifier is reported only once
../../gcc-4.2-20060806/gcc/fortran/parse.c:1601: error: for each function it appears in.)

Looking at parse.c, it appears that gfc_component has been removed from the parse_derived call breaking
the section of the patch that looks for allocatable components.
Comment 15 eedelman 2006-08-09 21:55:19 UTC
Created attachment 12049 [details]
Updated patch

Fix the problem reported by Jack.
Comment 16 Jack Howarth 2006-08-10 13:31:39 UTC
My first attempt to build with this revised patch was unsuccessful...

/sw/src/fink.build/gcc4-4.1.999-20060809/darwin_objdir/./gcc/xgcc -B/sw/src/fink.build/gcc4-4.1.999-20060809/darwin_objdir/./gcc/ -B/sw/lib/gcc4/powerpc-apple-darwin8/bin/ -B/sw/lib/gcc4/powerpc-apple-darwin8/lib/ -isystem /sw/lib/gcc4/powerpc-apple-darwin8/include -isystem /sw/lib/gcc4/powerpc-apple-darwin8/sys-include -DHAVE_CONFIG_H -I. -I../../../gcc-4.2-20060809/libgfortran -I. -iquote../../../gcc-4.2-20060809/libgfortran/io -I../../../gcc-4.2-20060809/libgfortran/../gcc -I../../../gcc-4.2-20060809/libgfortran/../gcc/config -I../.././gcc -D_GNU_SOURCE -std=gnu99 -Wall -Wstrict-prototypes -Wmissing-prototypes -Wold-style-definition -Wextra -Wwrite-strings -O2 -g -O2 -c ../../../gcc-4.2-20060809/libgfortran/intrinsics/malloc.c -o malloc.o >/dev/null 2>&1
make[3]: *** No rule to make target `intrinsics/move_alloc.c', needed by `move_alloc.lo'.  Stop.
make[2]: *** [all] Error 2
make[1]: *** [all-target-libgfortran] Error 2
make: *** [all] Error 2
### execution of /var/tmp/tmp.2.82ybS7 failed, exit code 2
Failed: phase compiling: gcc4-4.1.999-20060809 failed


I'll double check that I didn't drop any part of the patch by accident
but I do recall any errors when patching.



(In reply to comment #15)
> Created an attachment (id=12049) [edit]
> Updated patch
> 
> Fix the problem reported by Jack.
> 

Comment 17 eedelman 2006-08-10 20:23:14 UTC
Created attachment 12060 [details]
New version.

Yup, the previous patch wasn't complete (it lacked libgfortran/intrinsics/move_alloc.c); this one should be better.  It also addresses the issue pointed out by Thomas Koenig at 2006-05-09.

Thanks for testing!
Comment 18 Jack Howarth 2006-08-20 14:37:25 UTC
With the latest changes to gcc/fortran/trans-expr.c the current proposed patch no longer applies. The code which is tangling up the patch is...

***************
*** 2664,2683 ****
      }
    else if (cm->dimension)
      {
-       tmp = gfc_trans_subarray_assign (dest, cm, expr);
-       gfc_add_expr_to_block (&block, tmp);
      }
    else if (expr->ts.type == BT_DERIVED)
      {
        /* Nested derived type.  */
-       tmp = gfc_trans_structure_assign (dest, expr);
        gfc_add_expr_to_block (&block, tmp);
      }
    else
      {
        /* Scalar component.  */
-       gfc_se lse;
- 
        gfc_init_se (&se, NULL);
        gfc_init_se (&lse, NULL);
  
where we now have an additional "if (expr->expr_type != EXPR_STRUCTURE)" inserted. Is the current proposed patch still valid in this section with minor adjustments so that it applies or will the proposed code have to be modified due to the changes here?
Comment 19 eedelman 2006-08-20 17:38:18 UTC
Created attachment 12106 [details]
Updated patch

Fixes the conflicts with recently committed patches.
Comment 20 Andrew Pinski 2006-09-19 16:41:11 UTC
*** Bug 29142 has been marked as a duplicate of this bug. ***
Comment 21 Paul Thomas 2006-09-23 16:18:47 UTC
Created attachment 12313 [details]
Latest patch

This version fixes the problem with constructors of structures that have allocatable components of structures with allocatable components.  It also fixes Salvatore's problem with initializers (thanks!). Finally, the problems with forall seem to have fixed themeselves...,I think.

Paul
Comment 22 Jack Howarth 2006-09-23 16:24:39 UTC
Paul,
    Could you please include the testsuite testcases when you post the
patch? It's rather hard to regression test without those.
             Jack
Comment 23 Jack Howarth 2006-09-23 18:41:04 UTC
Paul,
     The new patch doesn't allow gfortran to build. I get an error...

/sw/src/fink.build/gcc4-4.1.9999-20060923/darwin_objdir/./prev-gcc/xgcc -B/sw/src/fink.build/gcc4-4.1.9999-20060923/darwin_objdir/./prev-gcc/ -B/sw/lib/gcc4/powerpc-apple-darwin8/bin/ -c   -g -O2 -mdynamic-no-pic -DIN_GCC   -W -Wall -Wwrite-strings -Wstrict-prototypes -Wmissing-prototypes -pedantic -Wno-long-long -Wno-variadic-macros -Wno-overlength-strings -Wold-style-definition -Wmissing-format-attribute -Werror -fno-common   -DHAVE_CONFIG_H -I. -Ifortran -I../../gcc-4.2-20060923/gcc -I../../gcc-4.2-20060923/gcc/fortran -I../../gcc-4.2-20060923/gcc/../include -I./../intl -I../../gcc-4.2-20060923/gcc/../libcpp/include -I/sw/include  -I../../gcc-4.2-20060923/gcc/../libdecnumber -I../libdecnumber -I/sw/include   ../../gcc-4.2-20060923/gcc/fortran/trans-expr.c -o fortran/trans-expr.o
../../gcc-4.2-20060923/gcc/fortran/trans-expr.c: In function 'gfc_conv_structure':
../../gcc-4.2-20060923/gcc/fortran/trans-expr.c:2902: error: 'gfc_constructor' has no member named 'allocatable'
make[3]: *** [fortran/trans-expr.o] Error 1
make[2]: *** [all-stage2-gcc] Error 2
make[1]: *** [stage2-bubble] Error 2
make: *** [all] Error 2
Comment 24 Paul Thomas 2006-09-24 17:31:08 UTC
Created attachment 12320 [details]
Patch + testcases for allocatable components

This version has all the known issues fixed and includes a number of testcases - some complete and some in 'draft' form.

We are nearly there!

Paul
Comment 25 Jack Howarth 2006-09-25 05:09:58 UTC
Paul,
    The current patch builds fine on Darwin PPC and shows no regressions
in the gfortran testsuite at either -m32 or -m64.
Comment 26 Jerry DeLisle 2006-09-25 05:53:49 UTC
Paul,

OK here too. i686-linux
Comment 27 Paul Thomas 2006-09-28 14:06:57 UTC
Created attachment 12350 [details]
The latest version, incorporating all fixes so far.

This latest has an increasingly complete set of testcases and fixes for the problems found by Salvatore Filippone.

What is missing is the setting of scalar assignment flags for WHERE blocks/statements and another attempt to understand what is broken with zero length strings (for iso_varying_string).

A ChangeLog exists, which is about two days behind.

Paul
Comment 28 Paul Thomas 2006-09-29 15:00:31 UTC
Created attachment 12354 [details]
Patch that fixes Salvatore's latest

This patch moves the addition of EXPR_NULL for allocatable components to expr.c(gfc_default_initializer).  The consequence of this is that ALL structures with allocatable components get a default initializer, even if it only contains EXPR_NULL. Whilst this is OK for the static initialization, it is unnecessary because of the nullification that is done upon coming into scope.  Thus, translation of such intitializer expressions is skipped in trans-expr.c(gfc_conv_structure).

ALLOCATE now does an assignment of this potentially compound default initializer expression to each and every allocatable component.  Being a variable assignment, this produces extra code that checks for non-NULL data fields to see if they should be deallocated.  This ups the dealloactions counted by alloc_comp_basics_1.f90 to 38.

With this modification, the patch regtests OK.

Paul
Comment 29 Jack Howarth 2006-10-02 03:10:45 UTC
Latest version builds fine and shows no regressions on Darwin PPC at -m32 and -m64.
Comment 30 Jerry DeLisle 2006-10-02 04:15:28 UTC
alloc_comps0929.diff tests OK for me on i686-linux.  
Comment 31 Salvatore Filippone 2006-10-02 07:21:31 UTC
For the record: my test application runs to completion with good results snapshot 20060930 + alloc_comps0929.diff. 
Comment 32 Paul Thomas 2006-10-02 21:54:07 UTC
Created attachment 12373 [details]
A patch that fixes test_ab9.f90

You will see the modification in trans-types.c.  This is the first bit of the patch that is not specific to allocatable components, although I am hard pressed to find a case that doesn't involve them.  If you feel uncomfortable with breaking the hermetic seal, I could make it specific.  That said, this does regtest OK, including all , the other derived type association tests.

I will write a test case tomorrow sometime and so have included my reduced version of test_ab9.f90 from Slavatore Filippone to ensure that the audit trail makes sense.

The problem arises because of the assignment that is used to initialize the INTENT(OUT) derived type in gfc_conv_function_call. This exercises an association that, I think, would not otherwise be possible.  It is fixed by usin the current namespace to start the search for like types, from any namespace where there is no parent.  The case where the derived type found is the same as 'self' is eliminated from the search by a continue statement.

Paul

module modA
  type dt
     integer, allocatable :: i(:)
  end type dt
end module modA

Module modB
  interface
     subroutine foo(x)
       use modA
       type(dt), intent(out)   :: x
     end subroutine foo
  end interface
end module modB

subroutine test_ab9()
  use modB ! putting this after USE modA clears the problem
  use modA

  type(dt)              :: a

  call foo(a)

  return

end subroutine test_ab9
Comment 33 Salvatore Filippone 2006-10-03 15:48:59 UTC
The latest patch alloc_comp1002.diff has survived everything I could throw at it in the last few hours. Go for it. 
Comment 34 patchapp@dberlin.org 2006-10-05 05:00:51 UTC
Subject: Bug number PR20541

A patch for this bug has been added to the patch tracker.
The mailing list url for the patch is http://gcc.gnu.org/ml/gcc-patches/2006-10/msg00231.html
Comment 35 Paul Thomas 2006-10-08 16:22:20 UTC
Subject: Bug 20541

Author: pault
Date: Sun Oct  8 16:21:55 2006
New Revision: 117558

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=117558
Log:
2006-10-05  Erik Edelmann <edelmann@gcc.gnu.org>
	    Paul Thomas <pault@gcc.gnu.org>

	PR fortran/20541
	* interface.c (gfc_compare_derived_types): Add comparison of
	the allocatable field.
	* intrinsic.c (add_subroutines): Add MOVE_ALLOC.
	* trans-expr.c (gfc_conv_aliased_arg, gfc_trans_subarray_assign,
	gfc_trans_subcomponent_assign, gfc_conv_string_parameter,
	gfc_trans_scalar_assign): Add extra arguments l_is_temp
	and r_is_var to references to latter function.
	(gfc_conv_function_call): Add enum for types of argument and
	an associated variable parm_kind. Deallocate components of
	INTENT(OUT) and non-variable arrays.
	(gfc_trans_subcomponent_assign): Add block to assign arrays
	to allocatable components.
	(gfc_trans_scalar_assign): Add block to handle assignments of
	derived types with allocatable components, using the above new
	arguments to control allocation/deallocation of memory and the
	copying of allocated arrays.
	* trans-array.c (gfc_array_allocate): Remove old identification 
	of pointer and replace with that of an allocatable array. Add
	nullify of structures with allocatable components. 
	(gfc_conv_array_initializer): Treat EXPR_NULL.
	(gfc_conv_array_parameter): Deallocate allocatable components
	of non-variable structures.
	(gfc_trans_dealloc_allocated): Use second argument of library
	deallocate to inhibit, without error, freeing NULL pointers.
	(get_full_array_size): New function to return the size of a
	full array.
	(gfc_duplicate_allocatable): New function to allocate and copy
	allocated data.
	(structure_alloc_comps): New recursive function to deallocate,
	nullify or copy allocatable components.
	(gfc_nullify_alloc_comp, gfc_deallocate_alloc_comp,
	gfc_copy_alloc_comp): New interface functions to call previous.
	(gfc_trans_deferred_array): Add the code to nullify allocatable
	components, when entering scope, and to deallocate them on
	leaving. Do not call gfc_trans_static_array_pointer and return
	for structures with allocatable components and default
	initializers.
	* symbol.c (gfc_set_component_attr): Set allocatable field.
	(gfc_get_component_attr): Set the allocatable attribute.
	* intrinsic.h : Prototype for gfc_check_move_alloc.
	* decl.c (build_struct): Apply TR15581 constraints for
	allocatable components.
	(variable_decl): Default initializer is always NULL for
	allocatable components.
	(match_attr_spec): Allow, or not, allocatable components,
	according to the standard in force.
	* trans-array.h : Prototypes for gfc_nullify_alloc_comp,
	gfc_deallocate_alloc_comp, gfc_copy_alloc_comp and
	gfc_duplicate_allocatable.
	* gfortran.texi : Add mention of TR15581 extensions.
	* gfortran.h : Add attribute alloc_comp, add
	gfc_components field allocatable and add the prototype
	for gfc_expr_to_initialize.
	* trans-stmt.c (generate_loop_for_temp_to_lhs,
	generate_loop_for_rhs_to_temp, gfc_trans_where_assign,
	gfc_trans_where_3): Add extra arguments to calls to
	gfc_trans_scalar_assign and set appropriately.
	(gfc_trans_allocate): Nullify allocatable components.
	(gfc_trans_deallocate): Deallocate to ultimate allocatable
	components but stop at ultimate pointer components.
	* module.c (mio_symbol_attribute, mio_symbol_attribute,
	mio_component): Add module support for allocatable
	components.
	* trans-types.c (gfc_get_derived_type): Treat allocatable
	components.
	* trans.h : Add two boolean arguments to
	gfc_trans_scalar_assign.
	* resolve.c (resolve_structure_cons): Check conformance of
	constructor element and the component.
	(resolve_allocate_expr): Add expression to nullify the
	constructor expression for allocatable components.
	(resolve_transfer): Inhibit I/O of derived types with
	allocatable components.
	(resolve_fl_derived): Skip check of bounds of allocatable
	components.
	* trans-decl.c (gfc_get_symbol_decl): Add derived types
	with allocatable components to deferred variable.
	(gfc_trans_deferred_vars): Make calls for derived types
	with allocatable components to gfc_trans_deferred_array.
	(gfc_generate_function_code): Nullify allocatable
	component function result on entry.
	* parse.c (parse_derived): Set symbol attr.allocatable if
	allocatable components are present.
	* check.c (gfc_check_allocated): Enforce attr.allocatable
	for intrinsic arguments.
	(gfc_check_move_alloc): Check arguments of move_alloc.
	* primary.c (gfc_variable_attr): Set allocatable attribute.
	* intrinsic.texi : Add index entry and section for
	for move_alloc.

	PR fortran/29115
	* resolve.c (resolve_structure_cons): It is an error if the
	pointer component elements of a derived type constructor are
	not pointer or target.


	PR fortran/29211
	* trans-stmt.c (generate_loop_for_temp_to_lhs,
	generate_loop_for_rhs_to_temp): Provide a string length for
	the temporary by copying that of the other side of the scalar
	assignment.


2006-10-05  Paul Thomas  <pault@gcc.gnu.org>
	    Erik Edelmann  <edelmann@gcc.gnu.org>

	PR libgfortran/20541
	* Makefile.in : Add move_alloc.
	* intrinsics/move_alloc.c: New function.
	* Makefile.am : Add move_alloc.



2006-10-05  Erik Edelmann  <edelmann@gcc.gnu.org>
	    Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/20541
	* gfortran.dg/alloc_comp_basics_1.f90: New test.
	* gfortran.dg/alloc_comp_basics_2.f90: New test.
	* gfortran.dg/alloc_comp_assign_1.f90: New test.
	* gfortran.dg/alloc_comp_assign_2.f90: New test.
	* gfortran.dg/alloc_comp_assign_3.f90: New test.
	* gfortran.dg/alloc_comp_assign_4.f90: New test.
	* gfortran.dg/alloc_comp_constraint_1.f90: New test.
	* gfortran.dg/alloc_comp_constraint_2.f90: New test.
	* gfortran.dg/alloc_comp_constraint_3.f90: New test.
	* gfortran.dg/alloc_comp_constructor_1.f90: New test.
	* gfortran.dg/alloc_comp_constructor_2.f90: New test.
	* gfortran.dg/alloc_comp_initializer_1.f90: New test.
	* gfortran.dg/alloc_comp_std.f90: New test.
	* gfortran.dg/move_alloc.f90: New test.

	PR fortran/29115
	* gfortran.dg/derived_constructor_comps_2.f90: New test.

	PR fortran/29211
	* gfortran.dg/forall_char_dependencies_1.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_assign_1.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_assign_2.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_assign_3.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_assign_4.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_basics_1.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_basics_2.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_constraint_1.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_constraint_2.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_constraint_3.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_constructor_1.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_constructor_2.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_initializer_1.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_initializer_2.f90
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_std.f90
    trunk/gcc/testsuite/gfortran.dg/derived_constructor_comps_2.f90
    trunk/gcc/testsuite/gfortran.dg/forall_char_dependencies_1.f90
    trunk/gcc/testsuite/gfortran.dg/move_alloc.f90
    trunk/libgfortran/intrinsics/move_alloc.c
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/check.c
    trunk/gcc/fortran/decl.c
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/interface.c
    trunk/gcc/fortran/intrinsic.c
    trunk/gcc/fortran/intrinsic.h
    trunk/gcc/fortran/intrinsic.texi
    trunk/gcc/fortran/module.c
    trunk/gcc/fortran/parse.c
    trunk/gcc/fortran/primary.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/symbol.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-array.h
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/fortran/trans-types.c
    trunk/gcc/fortran/trans.h
    trunk/gcc/testsuite/ChangeLog
    trunk/libgfortran/ChangeLog
    trunk/libgfortran/Makefile.in

Comment 36 Paul Thomas 2006-10-08 16:27:43 UTC
Fixed in gcc-4.2

Paul and Erik
Comment 37 Paul Thomas 2006-10-16 22:29:58 UTC
Subject: Bug 20541

Author: pault
Date: Mon Oct 16 22:29:46 2006
New Revision: 117797

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=117797
Log:
2006-10-17  Paul Thomas <pault@gcc.gnu.org>

	PR fortran/20541
	* trans-array.c (gfc_trans_array_bounds): Test for and set
	negative stride of a non-constant bound array to zero.

	PR fortran/29392
	* data.c (create_character_intializer): Copy and simplify
	the expressions for the start and end of a sub-string
	reference.

2006-10-17  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/29392
	* gfortran.dg/data_char_3.f90: New test.

	PR fortran/20541
	* gfortran.dg/negative_automatic_size.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/data_char_3.f90
    trunk/gcc/testsuite/gfortran.dg/negative_automatic_size.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/data.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/testsuite/ChangeLog

Comment 38 Paul Thomas 2006-10-17 11:33:51 UTC
(In reply to comment #37)
Sorry all, I screwed up on the PR number - it should have been 29541

Paul