OSDN Git Service

2010-04-24 Kai Tietz <kai.tietz@onevision.com>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / pr43984.f90
1 ! { dg-do compile }
2 ! { dg-options "-O2 -fno-tree-dominator-opts -fdump-tree-pre" }
3 module test
4
5    type shell1quartet_type
6
7    integer(kind=kind(1)) :: ab_l_sum
8    integer(kind=kind(1)), dimension(:), pointer :: ab_form_3dints_x_indices => NULL()
9    integer(kind=kind(1)), dimension(:), pointer :: ab_form_3dints_yz_rms_indices => NULL()
10
11     end type
12
13 contains
14 subroutine make_esss(self,esss)
15   type(shell1quartet_type) :: self
16   intent(in) :: self
17   real(kind=kind(1.0d0)), dimension(:), intent(out) :: esss
18   real(kind=kind(1.0d0)), dimension(:), pointer :: Izz
19   real(kind=kind(1.0d0)), dimension(:,:), pointer :: Ix,Iy,Iz,Iyz
20   integer(kind=kind(1)), dimension(:), pointer  :: e_x,ii_ivec
21   integer(kind=kind(1)) :: dim, dim1, nroots, ii,z,y
22
23     dim = self%ab_l_sum+1
24     dim1 = self%ab_l_sum+2
25     nroots = (dim1) / 2
26     call create_(Ix,nroots,dim)
27     call create_(Iy,nroots,dim)
28     call create_(Iz,nroots,dim)
29     call create_(Iyz,nroots,dim*dim1/2)
30
31     e_x => self%ab_form_3dints_x_indices
32     ii_ivec => self%ab_form_3dints_yz_rms_indices
33
34     call foo(Ix)
35     call foo(Iy)
36     call foo(Iz)
37
38     esss = ZERO
39     ii = 0
40     do z=1,dim
41       Izz => Iz(:,z)
42       do y=1,dim1-z
43         ii = ii + 1
44         Iyz(:,ii) = Izz * Iy(:,y)
45       end do
46     end do
47     esss = esss + sum(Ix(:,e_x) * Iyz(:,ii_ivec),1)
48
49 end subroutine
50
51 end
52
53 ! There should be three loads from iyz.data, not four.
54
55 ! { dg-final { scan-tree-dump-times "= iyz.data" 3 "pre" } }
56 ! { dg-final { cleanup-tree-dump "pre" } }