~madteam/mg5amcnlo/series2.0

« back to all changes in this revision

Viewing changes to vendor/IREGI/src/cpave_reduce.f90

  • Committer: olivier Mattelaer
  • Date: 2015-03-05 00:14:16 UTC
  • mfrom: (258.1.9 2.3)
  • mto: (258.8.1 2.3)
  • mto: This revision was merged to the branch mainline in revision 259.
  • Revision ID: olivier.mattelaer@uclouvain.be-20150305001416-y9mzeykfzwnl9t0j
partial merge

Show diffs side-by-side

added added

removed removed

Lines of Context:
25
25
    INTEGER,DIMENSION(0:NLOOPLINE)::indices0,indices00
26
26
    COMPLEX(KIND(1d0)),DIMENSION(1:4)::sumf
27
27
    REAL(KIND(1d0))::factor,factor0
28
 
    INTEGER,DIMENSION(1,1)::xitemp1
29
 
    INTEGER,DIMENSION(6,2)::xitemp2
30
 
    INTEGER,DIMENSION(21,3)::xitemp3
31
 
    INTEGER,DIMENSION(56,4)::xitemp4
32
 
    INTEGER,DIMENSION(126,5)::xitemp5
33
 
    REAL(KIND(1d0)),DIMENSION(126)::factor_xi
 
28
    TYPE xitemptype
 
29
       INTEGER::dim1,dim2
 
30
       INTEGER,DIMENSION(:,:),ALLOCATABLE::xitempi
 
31
    END TYPE xitemptype
 
32
    TYPE(xitemptype),DIMENSION(MAXNLOOP_IREGI-1)::xitemp
 
33
    REAL(KIND(1d0)),DIMENSION(:),ALLOCATABLE::factor_xi
34
34
    LOGICAL::find
 
35
    INTEGER::init=0
 
36
    SAVE init,xitemp,factor_xi
35
37
    TYPE(cibppave_node),POINTER::item
36
38
    pave(1:4)=DCMPLX(0d0)
37
39
    IF(.NOT.STABLE_IREGI)RETURN
54
56
          RETURN
55
57
       ENDIF
56
58
    ENDIF
 
59
    IF(init.EQ.0)THEN
 
60
       DO i=1,MAXNLOOP_IREGI-1
 
61
          xitemp(i)%dim2=i
 
62
          xitemp(i)%dim1=xiarray_arg1(MAXRANK_IREGI,i)
 
63
          IF(.NOT.ALLOCATED(xitemp(i)%xitempi))THEN
 
64
             ALLOCATE(xitemp(i)%xitempi(xitemp(i)%dim1,xitemp(i)%dim2))
 
65
          ENDIF
 
66
       ENDDO
 
67
       IF(.NOT.ALLOCATED(factor_xi))THEN
 
68
          j=xiarray_arg1(MAXRANK_IREGI,MAXNLOOP_IREGI-1)
 
69
          ALLOCATE(factor_xi(j))
 
70
       ENDIF
 
71
       init=1
 
72
    ENDIF
57
73
    mom(0:3)=PCL(1,0:3)
58
74
    IF(NLOOPLINE.GE.2)THEN
59
75
       indices0(0:NLOOPLINE)=paveindices(0:NLOOPLINE)
85
101
             SELECT CASE(NLOOPLINE-1)
86
102
             CASE(1)
87
103
                ntot=1
88
 
                CALL all_integers(NLOOPLINE-1,ntot,i,xitemp1(1:ntot,1:1),&
89
 
                     factor_xi(1:ntot))
90
 
                DO j=1,ntot
91
 
                   indices00(0:NLOOPLINE)=indices0(0:NLOOPLINE)
92
 
                   indices00(2:NLOOPLINE)=indices00(2:NLOOPLINE)&
93
 
                        +xitemp1(j,1:1)
94
 
                   sumf(1:4)=sumf(1:4)+factor_xi(j)*&
95
 
                        comp_pavefun_reduce(NLOOPLINE,indices00,PCL1,M2L)
96
 
                ENDDO
97
 
             CASE(2)
98
 
                ntot=ntot_xiarray(i,2)
99
 
                CALL all_integers(NLOOPLINE-1,ntot,i,&
100
 
                     xitemp2(1:ntot,1:2),factor_xi(1:ntot))
101
 
                DO j=1,ntot
102
 
                   indices00(0:NLOOPLINE)=indices0(0:NLOOPLINE)
103
 
                   indices00(2:NLOOPLINE)=indices00(2:NLOOPLINE)&
104
 
                        +xitemp2(j,1:2)
105
 
                   sumf(1:4)=sumf(1:4)+factor_xi(j)*&
106
 
                        comp_pavefun_reduce(NLOOPLINE,indices00,PCL1,M2L)
107
 
                ENDDO
108
 
             CASE(3)
109
 
                ntot=ntot_xiarray(i,3)
110
 
                CALL all_integers(NLOOPLINE-1,ntot,i,&
111
 
                     xitemp3(1:ntot,1:3),factor_xi(1:ntot))
112
 
                DO j=1,ntot
113
 
                   indices00(0:NLOOPLINE)=indices0(0:NLOOPLINE)
114
 
                   indices00(2:NLOOPLINE)=indices00(2:NLOOPLINE)&
115
 
                        +xitemp3(j,1:3)
116
 
                   sumf(1:4)=sumf(1:4)+factor_xi(j)*&
117
 
                        comp_pavefun_reduce(NLOOPLINE,indices00,PCL1,M2L)
118
 
                ENDDO
119
 
             CASE(4)
120
 
                ntot=ntot_xiarray(i,4)
121
 
                CALL all_integers(NLOOPLINE-1,ntot,i,&
122
 
                     xitemp4(1:ntot,1:4),factor_xi(1:ntot))
123
 
                DO j=1,ntot
124
 
                   indices00(0:NLOOPLINE)=indices0(0:NLOOPLINE)
125
 
                   indices00(2:NLOOPLINE)=indices00(2:NLOOPLINE)&
126
 
                        +xitemp4(j,1:4)
127
 
                   sumf(1:4)=sumf(1:4)+factor_xi(j)*&
128
 
                        comp_pavefun_reduce(NLOOPLINE,indices00,PCL1,M2L)
129
 
                ENDDO
130
 
             CASE(5)
131
 
                ntot=ntot_xiarray(i,5)
132
 
                CALL all_integers(NLOOPLINE-1,ntot,i,&
133
 
                     xitemp5(1:ntot,1:5),factor_xi(1:ntot))
134
 
                DO j=1,ntot
135
 
                   indices00(0:NLOOPLINE)=indices0(0:NLOOPLINE)
136
 
                   indices00(2:NLOOPLINE)=indices00(2:NLOOPLINE)&
137
 
                        +xitemp5(j,1:5)
 
104
                CALL all_integers(NLOOPLINE-1,ntot,i,xitemp(1)%xitempi(1:ntot,1:1),&
 
105
                     factor_xi(1:ntot))
 
106
                DO j=1,ntot
 
107
                   indices00(0:NLOOPLINE)=indices0(0:NLOOPLINE)
 
108
                   indices00(2:NLOOPLINE)=indices00(2:NLOOPLINE)&
 
109
                        +xitemp(1)%xitempi(j,1:1)
 
110
                   sumf(1:4)=sumf(1:4)+factor_xi(j)*&
 
111
                        comp_pavefun_reduce(NLOOPLINE,indices00,PCL1,M2L)
 
112
                ENDDO
 
113
             CASE DEFAULT
 
114
                ntot=ntot_xiarray(i,NLOOPLINE-1)
 
115
                CALL all_integers(NLOOPLINE-1,ntot,i,&
 
116
                     xitemp(NLOOPLINE-1)%xitempi(1:ntot,1:NLOOPLINE-1),&
 
117
                     factor_xi(1:ntot))
 
118
                DO j=1,ntot
 
119
                   indices00(0:NLOOPLINE)=indices0(0:NLOOPLINE)
 
120
                   indices00(2:NLOOPLINE)=indices00(2:NLOOPLINE)&
 
121
                        +xitemp(NLOOPLINE-1)%xitempi(j,1:NLOOPLINE-1)
138
122
                   sumf(1:4)=sumf(1:4)+factor_xi(j)*&
139
123
                        comp_pavefun_reduce(NLOOPLINE,indices00,PCL1,M2L)
140
124
                ENDDO
189
173
    COMPLEX(KIND(1d0)),DIMENSION(2,2)::xxList2
190
174
    COMPLEX(KIND(1d0)),DIMENSION(3,3)::xxList3
191
175
    INTEGER::ll1,ll2,ll3
192
 
    INTEGER,DIMENSION(10)::llarray
 
176
    INTEGER,DIMENSION(MAXNLOOP_IREGI*MAXINDICES_IREGI)::llarray
193
177
    TYPE(cibppave_node),POINTER::item
194
178
    LOGICAL::find
195
179
    pave(1:4)=DCMPLX(0d0)
1426
1410
                ENDIF
1427
1411
                RETURN
1428
1412
             ENDIF
1429
 
          ELSE
 
1413
          ELSEIF(ii+jj+kk+ll.LT.6)THEN
1430
1414
             ! Generalization of Eq.(6.18), (6.19), (6.20), (6.21)
1431
1415
             CALL CXYZMATRICES(NLOOPLINE,PCL,M2L,&
1432
1416
                  XMATRIX,YMATRIX,ZMATRIX,detY,detZ)
1433
1417
             IF(ABS(detY).GE.EPS)THEN
1434
1418
                ss=ii+jj+kk+ll
1435
 
                IF(ss.GT.10)THEN
 
1419
                IF(ss.GT.MAXNLOOP_IREGI*MAXINDICES_IREGI)THEN
1436
1420
                   WRITE(*,*)"ERROR: out of range of llarray in comp_pavefun_reduce"
1437
1421
                   STOP
1438
1422
                ENDIF
1531
1515
          ENDIF
1532
1516
       ENDIF
1533
1517
       IF(lind.EQ.0.AND.paveindices(2).EQ.0.AND.paveindices(3).EQ.0&
1534
 
            .AND.paveindices(4).EQ.0.AND.paveindices(5).EQ.0)THEN
 
1518
            .AND.paveindices(4).EQ.0.AND.paveindices(5).EQ.0.AND.&
 
1519
            paveindices(0).LT.6)THEN
1535
1520
          ! Generalization of Eq.(6.18) and Eq.(6.20)
1536
1521
          CALL CXYZMATRICES(NLOOPLINE,PCL,M2L,&
1537
1522
               XMATRIX,YMATRIX,ZMATRIX,detY,detZ)
1644
1629
                ENDIF
1645
1630
                RETURN
1646
1631
             ENDIF
1647
 
          ELSE
 
1632
          ELSEIF(ss.LT.4)THEN
1648
1633
             ! Generalization of Eq.(6.20) and Eq.(6.21)
1649
1634
             CALL CXYZMATRICES(NLOOPLINE,PCL,M2L,&
1650
1635
                  XMATRIX,YMATRIX,ZMATRIX,detY,detZ)
1657
1642
                RETURN
1658
1643
             ENDIF
1659
1644
             ss=ss+2
1660
 
             IF(ss.GT.12)THEN
 
1645
             IF(ss.GT.MAXNLOOP_IREGI*MAXINDICES_IREGI+2)THEN
1661
1646
                WRITE(*,*)"ERROR: out of range of llarray in comp_pavefun_reduce"
1662
1647
                STOP
1663
1648
             ENDIF
1901
1886
                ENDIF
1902
1887
                RETURN
1903
1888
             ENDIF
1904
 
             IF(ss.GT.10)THEN
 
1889
             IF(ss.GT.MAXNLOOP_IREGI*MAXINDICES_IREGI)THEN
1905
1890
                WRITE(*,*)"ERROR: out of range of llarray in comp_pavefun_reduce"
1906
1891
                STOP
1907
1892
             ENDIF
2002
1987
             RETURN
2003
1988
          ENDIF
2004
1989
          PP=ss+paveindices(0)
2005
 
          IF(PP.GT.10)THEN
 
1990
          IF(PP.GT.MAXNLOOP_IREGI*MAXINDICES_IREGI)THEN
2006
1991
             WRITE(*,*)"ERROR: out of range of llarray in comp_pavefun_reduce"
2007
1992
             STOP
2008
1993
          ENDIF
2063
2048
             RETURN
2064
2049
          ENDIF
2065
2050
          PP=ss+paveindices(0)
2066
 
          IF(PP.GT.10)THEN
 
2051
          IF(PP.GT.MAXNLOOP_IREGI*MAXINDICES_IREGI)THEN
2067
2052
             WRITE(*,*)"ERROR: out of range of llarray in comp_pavefun_reduce"
2068
2053
             STOP
2069
2054
          ENDIF