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] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }! Tests the fix for PR34820, in which the nullification of the! automatic array iregion occurred in the caller, rather than the! callee. Since 'nproc' was not available, an ICE ensued. During! the bug fix, it was found that the scalar to array assignment! of derived types with allocatable components did not work and! the fix of this is tested too.!! Contributed by Toon Moene <toon@moene.indiv.nluug.nl>!module grid_iotype grid_index_regioninteger, allocatable::lons(:)end type grid_index_regioncontainssubroutine read_grid_header()integer :: npiece = 1type(grid_index_region),allocatable :: iregion(:)allocate (iregion(npiece + 1))call read_iregion(npiece,iregion)if (size(iregion) .ne. npiece + 1) call abortif (.not.allocated (iregion(npiece)%lons)) call abortif (allocated (iregion(npiece+1)%lons)) call abortif (any (iregion(npiece)%lons .ne. [(i, i = 1, npiece)])) call abortdeallocate (iregion)end subroutine read_grid_headersubroutine read_iregion (nproc,iregion)integer,intent(in)::nproctype(grid_index_region), intent(OUT)::iregion(1:nproc)integer :: iarg(nproc)iarg = [(i, i = 1, nproc)]iregion = grid_index_region (iarg) !end subroutine read_iregionend module grid_iouse grid_iocall read_grid_headerend! { dg-final { cleanup-tree-dump "grid_io" } }! { dg-final { cleanup-modules "grid_io" } }
