OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [alloc_comp_auto_array_2.f90] - Blame information for rev 749

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do run }
2
! Tests the fix for PR34820, in which the nullification of the
3
! automatic array iregion occurred in the caller, rather than the
4
! callee.  Since 'nproc' was not available, an ICE ensued. During
5
! the bug fix, it was found that the scalar to array assignment
6
! of derived types with allocatable components did not work and
7
! the fix of this is tested too.
8
!
9
! Contributed by Toon Moene 
10
!
11
module grid_io
12
  type grid_index_region
13
    integer, allocatable::lons(:)
14
  end type grid_index_region
15
contains
16
  subroutine read_grid_header()
17
    integer :: npiece = 1
18
    type(grid_index_region),allocatable :: iregion(:)
19
    allocate (iregion(npiece + 1))
20
    call read_iregion(npiece,iregion)
21
    if (size(iregion) .ne. npiece + 1) call abort
22
    if (.not.allocated (iregion(npiece)%lons)) call abort
23
    if (allocated (iregion(npiece+1)%lons)) call abort
24
    if (any (iregion(npiece)%lons .ne. [(i, i = 1, npiece)])) call abort
25
    deallocate (iregion)
26
  end subroutine read_grid_header
27
 
28
  subroutine read_iregion (nproc,iregion)
29
    integer,intent(in)::nproc
30
    type(grid_index_region), intent(OUT)::iregion(1:nproc)
31
    integer :: iarg(nproc)
32
    iarg = [(i, i = 1, nproc)]
33
    iregion = grid_index_region (iarg) !
34
  end subroutine read_iregion
35
end module grid_io
36
 
37
  use grid_io
38
  call read_grid_header
39
end
40
! { dg-final { cleanup-tree-dump "grid_io" } }
41
! { dg-final { cleanup-modules "grid_io" } }

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.