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_function_1.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do run }! { dg-options "-O2 -fdump-tree-original" }! Test ALLOCATABLE functions; the primary purpose here is to check that! each of the various types of reference result in the function result! being deallocated, using _gfortran_internal_free.! The companion, allocatable_function_1r.f90, executes this program.!subroutine moobar (a)integer, intent(in) :: a(:)if (.not.all(a == [ 1, 2, 3 ])) call abort()end subroutine moobarfunction foo2 (n)integer, intent(in) :: ninteger, allocatable :: foo2(:)integer :: iallocate (foo2(n))do i = 1, nfoo2(i) = iend doend function foo2module mcontainsfunction foo3 (n)integer, intent(in) :: ninteger, allocatable :: foo3(:)integer :: iallocate (foo3(n))do i = 1, nfoo3(i) = iend doend function foo3end module mprogram alloc_funuse mimplicit noneinteger :: a(3)interfacesubroutine moobar (a)integer, intent(in) :: a(:)end subroutine moobarend interfaceinterfacefunction foo2 (n)integer, intent(in) :: ninteger, allocatable :: foo2(:)end function foo2end interface! 2 _gfortran_internal_free'sif (.not.all(foo1(3) == [ 1, 2, 3 ])) call abort()a = foo1(size(a))! 1 _gfortran_internal_freeif (.not.all(a == [ 1, 2, 3 ])) call abort()call foobar(foo1(3))! 1 _gfortran_internal_freeif (.not.all(2*bar(size(a)) + 5 == [ 7, 9, 11 ])) call abort()! Although the rhs determines the loop size, the lhs reference is! evaluated, in case it has side-effects or is needed for bounds checking.! 3 _gfortran_internal_free'sa(1:size (bar (3))) = 2*bar(size(a)) + 2 + a(size (bar (3)))if (.not.all(a == [ 7, 9, 11 ])) call abort()! 3 _gfortran_internal_free'scall moobar(foo1(3)) ! internal functioncall moobar(foo2(3)) ! module functioncall moobar(foo3(3)) ! explicit interface! 9 _gfortran_internal_free's in totalcontainssubroutine foobar (a)integer, intent(in) :: a(:)if (.not.all(a == [ 1, 2, 3 ])) call abort()end subroutine foobarfunction foo1 (n)integer, intent(in) :: ninteger, allocatable :: foo1(:)integer :: iallocate (foo1(n))do i = 1, nfoo1(i) = iend doend function foo1function bar (n) result(b)integer, intent(in) :: ninteger, target, allocatable :: b(:)integer :: iallocate (b(n))do i = 1, nb(i) = iend doend function barend program alloc_fun! { dg-final { scan-tree-dump-times "free" 10 "original" } }! { dg-final { cleanup-tree-dump "original" } }! { dg-final { cleanup-modules "m" } }
