URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [generic_23.f03] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }! Test the fix for PR43945 in which the over-ridding of 'doit' and! 'getit' in type 'foo2' was missed in the specific binding to 'do' and 'get'.!! Contributed by Tobias Burnus <burnus@gcc.gnu.org>! and reported to clf by Salvatore Filippone <sfilippone@uniroma2.it>!module foo_modtype foointeger :: icontainsprocedure, pass(a) :: doitprocedure, pass(a) :: getitgeneric, public :: do => doitgeneric, public :: get => getitend type fooprivate doit,getitcontainssubroutine doit(a)class(foo) :: aa%i = 1write(*,*) 'FOO%DOIT base version'end subroutine doitfunction getit(a) result(res)class(foo) :: ainteger :: resres = a%iend function getitend module foo_modmodule foo2_moduse foo_modtype, extends(foo) :: foo2integer :: jcontainsprocedure, pass(a) :: doit => doit2procedure, pass(a) :: getit => getit2!!$ generic, public :: do => doit!!$ generic, public :: get => getitend type foo2private doit2, getit2containssubroutine doit2(a)class(foo2) :: aa%i = 2a%j = 3end subroutine doit2function getit2(a) result(res)class(foo2) :: ainteger :: resres = a%jend function getit2end module foo2_modprogram testd15use foo2_modtype(foo2) :: af2call af2%do()if (af2%i .ne. 2) call abortif (af2%get() .ne. 3) call abortend program testd15! { dg-final { cleanup-modules "foo_mod foo2_mod" } }
