URL
                    https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
                
            Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [allocatable_scalar_4.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do run }!! PR fortran/41872!!program testimplicit noneinteger, allocatable :: ainteger, allocatable :: ballocate(a)call foo(a)if(.not. allocated(a)) call abort()if (a /= 5) call abort()call bar(a)if (a /= 7) call abort()deallocate(a)if(allocated(a)) call abort()call check3(a)if(.not. allocated(a)) call abort()if(a /= 6874) call abort()call check4(a)if(.not. allocated(a)) call abort()if(a /= -478) call abort()allocate(b)b = 7482call checkOptional(.false.,.true., 7482)if (b /= 7482) call abort()call checkOptional(.true., .true., 7482, b)if (b /= 46) call abort()containssubroutine foo(a)integer, allocatable, intent(out) :: aif(allocated(a)) call abort()allocate(a)a = 5end subroutine foosubroutine bar(a)integer, allocatable, intent(inout) :: aif(.not. allocated(a)) call abort()if (a /= 5) call abort()a = 7end subroutine barsubroutine check3(a)integer, allocatable, intent(inout) :: aif(allocated(a)) call abort()allocate(a)a = 6874end subroutine check3subroutine check4(a)integer, allocatable, intent(inout) :: aif(.not.allocated(a)) call abort()if (a /= 6874) call abortdeallocate(a)if(allocated(a)) call abort()allocate(a)if(.not.allocated(a)) call abort()a = -478end subroutine check4subroutine checkOptional(prsnt, alloc, val, x)logical, intent(in) :: prsnt, allocinteger, allocatable, optional :: xinteger, intent(in) :: valif (present(x) .neqv. prsnt) call abort()if (present(x)) thenif (allocated(x) .neqv. alloc) call abort()end ifif (present(x)) thenif (allocated(x)) thenif (x /= val) call abort()end ifend ifcall checkOptional2(x)if (present(x)) thenif (.not. allocated(x)) call abort()if (x /= -6784) call abort()x = 46end ifcall checkOptional2()end subroutine checkOptionalsubroutine checkOptional2(x)integer, allocatable, optional, intent(out) :: xif (present(x)) thenif (allocated(x)) call abort()allocate(x)x = -6784end ifend subroutine checkOptional2end program test
