URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [alloc_comp_initializer_1.f90] - Rev 154
Compare with Previous | Blame | View Log
! { dg-do run }! This checks the correct functioning of derived types with default initializers! and allocatable components.!! Contributed by Salvatore Filippone <salvatore.filippone@uniroma2.it>!module p_type_modtype m_typeinteger, allocatable :: p(:)end type m_typetype basep_typetype(m_type), allocatable :: av(:)type(m_type), pointer :: ap => null ()integer :: i = 101end type basep_typetype p_typetype(basep_type), allocatable :: basepv(:)integer :: p1 , p2 = 1end type p_typeend module p_type_modprogram foouse p_type_modimplicit nonetype(m_type), target :: atype(p_type) :: pretype(basep_type) :: weecall test_ab8 ()a = m_type ((/101,102/))call p_bld (a, pre)if (associated (wee%ap) .or. wee%i /= 101) call abort ()wee%ap => aif (.not.associated (wee%ap) .or. allocated (wee%av)) call abort ()wee = basep_type ((/m_type ((/201, 202, 203/))/), null (), 99)if (.not.allocated (wee%av) .or. associated (wee%ap) .or. (wee%i .ne. 99)) call abort ()contains! Check that allocatable components are nullified after allocation.subroutine test_ab8 ()type(p_type) :: pinteger :: ierrif (.not.allocated(p%basepv)) thenallocate(p%basepv(1),stat=ierr)endifif (allocated (p%basepv) .neqv. .true.) call abort ()if (allocated (p%basepv(1)%av) .neqv. .false.) call abortif (p%basepv(1)%i .ne. 101) call abort ()end subroutine test_ab8subroutine p_bld (a, p)use p_type_modtype (m_type) :: atype(p_type) :: pif (any (a%p .ne. (/101,102/))) call abort ()if (allocated (p%basepv) .or. (p%p2 .ne. 1)) call abort ()end subroutine p_bldend program foo! { dg-final { cleanup-modules "p_type_mod" } }
