URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [dynamic_dispatch_10.f03] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }!! [OOP] Fortran runtime error: internal error: bad hash value in dynamic dispatch!! Contributed by David Car <david.car7@gmail.com>module BaseStrategytype, public, abstract :: Strategycontainsprocedure(strategy_update), pass( this ), deferred :: updateprocedure(strategy_pre_update), pass( this ), deferred :: preUpdateprocedure(strategy_post_update), pass( this ), deferred :: postUpdateend type Strategyabstract interfacesubroutine strategy_update( this )import Strategyclass (Strategy), target, intent(in) :: thisend subroutine strategy_updateend interfaceabstract interfacesubroutine strategy_pre_update( this )import Strategyclass (Strategy), target, intent(in) :: thisend subroutine strategy_pre_updateend interfaceabstract interfacesubroutine strategy_post_update( this )import Strategyclass (Strategy), target, intent(in) :: thisend subroutine strategy_post_updateend interfaceend module BaseStrategy!==============================================================================module LaxWendroffStrategyuse BaseStrategyprivate :: update, preUpdate, postUpdatetype, public, extends( Strategy ) :: LaxWendroffclass (Strategy), pointer :: child => null()containsprocedure, pass( this ) :: updateprocedure, pass( this ) :: preUpdateprocedure, pass( this ) :: postUpdateend type LaxWendroffcontainssubroutine update( this )class (LaxWendroff), target, intent(in) :: thisprint *, 'Calling LaxWendroff update'end subroutine updatesubroutine preUpdate( this )class (LaxWendroff), target, intent(in) :: thisprint *, 'Calling LaxWendroff preUpdate'end subroutine preUpdatesubroutine postUpdate( this )class (LaxWendroff), target, intent(in) :: thisprint *, 'Calling LaxWendroff postUpdate'end subroutine postUpdateend module LaxWendroffStrategy!==============================================================================module KEStrategyuse BaseStrategy! Uncomment the line below and it runs fine! use LaxWendroffStrategyprivate :: update, preUpdate, postUpdatetype, public, extends( Strategy ) :: KEclass (Strategy), pointer :: child => null()containsprocedure, pass( this ) :: updateprocedure, pass( this ) :: preUpdateprocedure, pass( this ) :: postUpdateend type KEcontainssubroutine init( this, other )class (KE), intent(inout) :: thisclass (Strategy), target, intent(in) :: otherthis % child => otherend subroutine initsubroutine update( this )class (KE), target, intent(in) :: thisif ( associated( this % child ) ) thencall this % child % update()end ifprint *, 'Calling KE update'end subroutine updatesubroutine preUpdate( this )class (KE), target, intent(in) :: thisif ( associated( this % child ) ) thencall this % child % preUpdate()end ifprint *, 'Calling KE preUpdate'end subroutine preUpdatesubroutine postUpdate( this )class (KE), target, intent(in) :: thisif ( associated( this % child ) ) thencall this % child % postUpdate()end ifprint *, 'Calling KE postUpdate'end subroutine postUpdateend module KEStrategy!==============================================================================program mainuse LaxWendroffStrategyuse KEStrategytype :: StratSeqclass (Strategy), pointer :: strat => null()end type StratSeqtype (LaxWendroff), target :: lw_strattype (KE), target :: ke_strattype (StratSeq), allocatable, dimension( : ) :: seqallocate( seq(10) )call init( ke_strat, lw_strat )call ke_strat % preUpdate()call ke_strat % update()call ke_strat % postUpdate()! call lw_strat % update()seq( 1 ) % strat => ke_stratseq( 2 ) % strat => lw_stratcall seq( 1 ) % strat % update()do i = 1, 2call seq( i ) % strat % update()end doend! { dg-final { cleanup-modules "basestrategy laxwendroffstrategy kestrategy" } }
