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/] [dynamic_dispatch_2.f03] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do run }! Tests dynamic dispatch of class subroutines.!! Contributed by Paul Thomas <pault@gcc.gnu.org>!module mtype :: t1integer :: i = 42procedure(make_real), pointer :: ptrcontainsprocedure, pass :: real => make_realprocedure, pass :: make_integerprocedure, pass :: prod => i_m_jgeneric, public :: extract => real, make_integergeneric, public :: base_extract => real, make_integerend type t1type, extends(t1) :: t2integer :: j = 99containsprocedure, pass :: real => make_real2procedure, pass :: make_integer_2procedure, pass :: prod => i_m_j_2generic, public :: extract => real, make_integer_2end type t2containssubroutine make_real (arg, arg2)class(t1), intent(in) :: argreal :: arg2arg2 = real (arg%i)end subroutine make_realsubroutine make_real2 (arg, arg2)class(t2), intent(in) :: argreal :: arg2arg2 = real (arg%j)end subroutine make_real2subroutine make_integer (arg, arg2, arg3)class(t1), intent(in) :: arginteger :: arg2, arg3arg3 = arg%i * arg2end subroutine make_integersubroutine make_integer_2 (arg, arg2, arg3)class(t2), intent(in) :: arginteger :: arg2, arg3arg3 = arg%j * arg2end subroutine make_integer_2subroutine i_m_j (arg, arg2)class(t1), intent(in) :: arginteger :: arg2arg2 = arg%iend subroutine i_m_jsubroutine i_m_j_2 (arg, arg2)class(t2), intent(in) :: arginteger :: arg2arg2 = arg%jend subroutine i_m_j_2end module muse mtype, extends(t1) :: l1character(16) :: chrend type l1class(t1), pointer :: a !=> NULL()type(t1), target :: btype(t2), target :: ctype(l1), target :: dreal :: rinteger :: ia => b ! declared typecall a%real(r)if (r .ne. real (42)) call abortcall a%prod(i)if (i .ne. 42) call abortcall a%extract (2, i)if (i .ne. 84) call abortcall a%base_extract (2, i)if (i .ne. 84) call aborta => c ! extension in modulecall a%real(r)if (r .ne. real (99)) call abortcall a%prod(i)if (i .ne. 99) call abortcall a%extract (3, i)if (i .ne. 297) call abortcall a%base_extract (3, i)if (i .ne. 126) call aborta => d ! extension in maincall a%real(r)if (r .ne. real (42)) call abortcall a%prod(i)if (i .ne. 42) call abortcall a%extract (4, i)if (i .ne. 168) call abortcall a%extract (4, i)if (i .ne. 168) call abortend! { dg-final { cleanup-modules "m" } }
