URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [pr43984.f90] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do compile }! { dg-options "-O2 -fno-tree-dominator-opts -fdump-tree-pre" }module testtype shell1quartet_typeinteger(kind=kind(1)) :: ab_l_suminteger(kind=kind(1)), dimension(:), pointer :: ab_form_3dints_x_indices => NULL()integer(kind=kind(1)), dimension(:), pointer :: ab_form_3dints_yz_rms_indices => NULL()end typecontainssubroutine make_esss(self,esss)type(shell1quartet_type) :: selfintent(in) :: selfreal(kind=kind(1.0d0)), dimension(:), intent(out) :: esssreal(kind=kind(1.0d0)), dimension(:), pointer :: Izzreal(kind=kind(1.0d0)), dimension(:,:), pointer :: Ix,Iy,Iz,Iyzinteger(kind=kind(1)), dimension(:), pointer :: e_x,ii_ivecinteger(kind=kind(1)) :: dim, dim1, nroots, ii,z,ydim = self%ab_l_sum+1dim1 = self%ab_l_sum+2nroots = (dim1) / 2call create_(Ix,nroots,dim)call create_(Iy,nroots,dim)call create_(Iz,nroots,dim)call create_(Iyz,nroots,dim*dim1/2)e_x => self%ab_form_3dints_x_indicesii_ivec => self%ab_form_3dints_yz_rms_indicescall foo(Ix)call foo(Iy)call foo(Iz)esss = ZEROii = 0do z=1,dimIzz => Iz(:,z)do y=1,dim1-zii = ii + 1Iyz(:,ii) = Izz * Iy(:,y)end doend doesss = esss + sum(Ix(:,e_x) * Iyz(:,ii_ivec),1)end subroutineend! There should be three loads from iyz.data, not four.! { dg-final { scan-tree-dump-times "= iyz.data" 3 "pre" } }! { dg-final { cleanup-tree-dump "pre" } }! { dg-final { cleanup-modules "test" } }
