~madteam/mg5amcnlo/series2.0

« back to all changes in this revision

Viewing changes to madgraph/iolibs/template_files/matrix_loop_induced_madevent.inc

  • 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:
 
1
SUBROUTINE SMATRIX%(proc_id)s(P,ANS)
 
2
C  
 
3
%(info_lines)s
 
4
 
5
C MadGraph5_aMC@NLO for Madevent Version
 
6
 
7
C Returns amplitude squared summed/avg over colors
 
8
c and helicities
 
9
c for the point in phase space P(0:3,NEXTERNAL)
 
10
C  
 
11
%(process_lines)s
 
12
 
13
    use DiscreteSampler
 
14
    IMPLICIT NONE
 
15
C  
 
16
C CONSTANTS
 
17
C  
 
18
    Include 'genps.inc'
 
19
    Include 'maxconfigs.inc'
 
20
    Include 'nexternal.inc'
 
21
    Include 'maxamps.inc'
 
22
    INTEGER                 NCOMB         
 
23
    PARAMETER (             NCOMB=%(ncomb)d)
 
24
    INTEGER    NLOOPDIAGRAMS
 
25
    PARAMETER (NLOOPDIAGRAMS=%(nloopdiags)d)
 
26
    INTEGER    NLOOPFLOWS
 
27
    PARAMETER (NLoopFlows=%(nLoopFlows)d) 
 
28
    INTEGER    THEL
 
29
    PARAMETER (THEL=NCOMB)
 
30
    INTEGER Hel_Average_Factor
 
31
    PARAMETER (Hel_Average_Factor=%(hel_avg_factor)d)
 
32
C  
 
33
C ARGUMENTS 
 
34
C  
 
35
    REAL*8 P(0:3,NEXTERNAL),ANS
 
36
c
 
37
c global (due to reading writting) 
 
38
c
 
39
        LOGICAL GOODHEL(NCOMB)
 
40
        INTEGER NTRY
 
41
        common/BLOCK_GOODHEL/NTRY,GOODHEL
 
42
C  
 
43
C LOCAL VARIABLES 
 
44
C  
 
45
    INTEGER NHEL(NEXTERNAL,NCOMB),NTRY
 
46
    REAL*8 T,MATRIX%(proc_id)s
 
47
    REAL*8 R,SUMHEL,TS(NCOMB)
 
48
    INTEGER I,IDEN
 
49
    INTEGER IPROC,JC(NEXTERNAL),II
 
50
    LOGICAL GOODHEL(NCOMB)
 
51
    REAL*8 HWGT, XTOT, XTRY, XREJ, XR, YFRAC(0:NCOMB)
 
52
    INTEGER IDUM, NGOOD, IGOOD(NCOMB), JHEL, J, JJ
 
53
    REAL     XRAN1
 
54
    EXTERNAL XRAN1
 
55
 
 
56
        REAL*8 , ALLOCATABLE :: ANS_ML(:,:)
 
57
    REAL*8 , ALLOCATABLE :: PREC_FOUND(:)
 
58
        INTEGER ML_RET_CODE
 
59
    INTEGER ML_ANS_DIMENSION
 
60
C Prec_found ans ans_ml are saved so that they don't have to be re-allocated everytime
 
61
        SAVE ML_ANS_DIMENSION,ANS_ML,PREC_FOUND
 
62
 
 
63
    DATA IDUM /-1/
 
64
    DATA XTRY, XREJ, NGOOD /0,0,0/
 
65
 
 
66
        LOGICAL INIT_MADLOOP
 
67
        DATA INIT_MADLOOP/.FALSE./
 
68
C  
 
69
C GLOBAL VARIABLES
 
70
C  
 
71
    LOGICAL FORCE_ML_HELICITY_SUM 
 
72
    common/to_ML_control/FORCE_ML_HELICITY_SUM 
 
73
 
 
74
    DOUBLE PRECISION AMP2(MAXAMPS), JAMP2(0:MAXFLOW)
 
75
    COMMON/TO_AMPS/  AMP2,       JAMP2
 
76
   
 
77
    CHARACTER*101        HEL_BUFF
 
78
    COMMON/TO_HELICITY/  HEL_BUFF
 
79
 
 
80
    %(real_dp_format)s ML_JAMP2(nLoopFlows)
 
81
        common/%(ml_prefix)sJAMP2/ML_JAMP2
 
82
 
 
83
    %(real_dp_format)s ML_AMP2(NLOOPDIAGRAMS)
 
84
        common/%(ml_prefix)sAMP2/ML_AMP2
 
85
    
 
86
    REAL*8 POL(2)
 
87
    COMMON/TO_POLARIZATION/ POL
 
88
    
 
89
    INTEGER          ISUM_HEL
 
90
    LOGICAL                    MULTI_CHANNEL
 
91
    COMMON/TO_MATRIX/ISUM_HEL, MULTI_CHANNEL
 
92
%(define_iconfigs_lines)s
 
93
    DATA XTRY, XREJ, NGOOD /0,0,0/
 
94
    SAVE YFRAC, IGOOD, JHEL
 
95
 
 
96
%(helicity_lines)s
 
97
 
 
98
C ----------
 
99
C BEGIN CODE
 
100
C ----------
 
101
 
 
102
        IF(NLOOPDIAGRAMS.GT.MAXAMPS) THEN
 
103
           STOP 'MAXAMPS smaller than to NLOOPDIAGRAMS in matrix.f'
 
104
        ENDIF
 
105
 
 
106
        IF(.NOT.INIT_MADLOOP) THEN
 
107
          INIT_MADLOOP = .TRUE.
 
108
C So that TIR integrals can be reused accross helicity configuration.
 
109
C Notice that ITR integrals for rotated PS points (i.e. which is part of MadLoop's default stabiliy test procedure), will not work. This is why one should always keep the MadLoop parameter 'NRotations_DP' set to 0.
 
110
          CALL %(ml_prefix)sSET_AUTOMATIC_TIR_CACHE_CLEARING(.FALSE.)
 
111
      CALL %(ml_prefix)sGET_ANSWER_DIMENSION(ML_ANS_DIMENSION)
 
112
      ALLOCATE(ANS_ML(0:3,0:ML_ANS_DIMENSION))
 
113
          ALLOCATE(PREC_FOUND(0:ML_ANS_DIMENSION))
 
114
        ENDIF
 
115
C But then we must clear the cache by hand at the beginning of the computation of each new PS point
 
116
        CALL %(ml_prefix)sCLEAR_TIR_CACHE()
 
117
   
 
118
        NTRY=NTRY+1
 
119
    DO I=1,NEXTERNAL
 
120
       JC(I) = +1
 
121
    ENDDO
 
122
     
 
123
    IF (multi_channel) THEN
 
124
        DO I=1,NLOOPDIAGRAMS
 
125
            AMP2(I)=0D0
 
126
        ENDDO
 
127
        JAMP2(0)=%(ncolor)d
 
128
        DO I=1,INT(JAMP2(0))
 
129
            JAMP2(I)=0D0
 
130
        ENDDO
 
131
    ENDIF
 
132
    ANS = 0D0
 
133
    WRITE(HEL_BUFF,'(20I5)') (0,I=1,NEXTERNAL)
 
134
 
 
135
    DO I=1,NCOMB
 
136
       TS(I)=0d0
 
137
    ENDDO
 
138
 
 
139
C  Notice that when forcing helicity sum directly in MadLoop then one doesn't have access to the weights of individual Hel. Configs so that they cannot be specified in the event file. We turned this option off by default.
 
140
    FORCE_ML_Helicity_Sum = (ISUM_HEL.eq.0.AND..False.)
 
141
    if (FORCE_ML_Helicity_Sum)then
 
142
C Of course this option can also not be used for polarized beams.
 
143
      do JJ=1,NINCOMING
 
144
            if (POL(JJ).NE.1d0) FORCE_ML_Helicity_Sum = .false.
 
145
          enddo        
 
146
    endif
 
147
 
 
148
    IF(Force_ML_Helicity_Sum )THEN
 
149
 
 
150
        CALL %(ml_prefix)sSLOOPMATRIX_THRES(P,ANS_ML,-1.0d0,PREC_FOUND,ML_RET_CODE)
 
151
                ANS = ANS_ML(1,0)
 
152
    
 
153
        ELSE
 
154
    IF (ISUM_HEL.EQ.0.or.(DS_get_dim_status('Helicity').eq.0)) THEN
 
155
           DO I=1,NCOMB
 
156
              IF (GOODHEL(I) .OR. NTRY .LE. MAXTRIES.OR.(ISUM_HEL.NE.0)) THEN
 
157
                        
 
158
                                CALL %(ml_prefix)sSLOOPMATRIXHEL_THRES(P,I,ANS_ML,-1.0d0,PREC_FOUND,ML_RET_CODE)
 
159
                                T = ANS_ML(1,0)                  
 
160
                DO JJ=1,JAMP2(0)
 
161
                  JAMP2(JJ) = JAMP2(JJ) + ML_JAMP2(JJ)
 
162
                ENDDO
 
163
                DO JJ=1,NLOOPDIAGRAMS
 
164
                  AMP2(JJ) = AMP2(JJ)+ ML_AMP2(JJ)
 
165
                ENDDO
 
166
 
 
167
                                DO JJ=1,nincoming
 
168
                     IF(POL(JJ).NE.1d0.AND.NHEL(JJ,I).EQ.INT(SIGN(1d0,POL(JJ)))) THEN
 
169
                         T=T*ABS(POL(JJ))
 
170
                     ELSE IF(POL(JJ).NE.1d0)THEN
 
171
                         T=T*(2d0-ABS(POL(JJ)))
 
172
                     ENDIF
 
173
                  ENDDO
 
174
                              IF (ISUM_HEL.NE.0) then
 
175
                                call DS_add_entry('Helicity',I,T)
 
176
                              endif
 
177
                  ANS=ANS+DABS(T)
 
178
                  TS(I)=T
 
179
              ENDIF
 
180
           ENDDO
 
181
                IF (ISUM_HEL.NE.0) then
 
182
!         We set HEL_PICKED to -1 here so that later on, the call to DS_add_point in dsample.f does not add anything to the grid since it was already done here.
 
183
                  HEL_PICKED = -1
 
184
!         For safety, hardset the helicity sampling jacobian to 0.0d0 to make sure it is not .
 
185
                  hel_jacobian   = 1.0d0
 
186
                  IF(DS_get_dim_status('Helicity').eq.1) then 
 
187
!           If we finished the initialization we can update the grid so as to start sampling over it.
 
188
!           However the grid will now be filled by dsample with different kind of weights (including pdf, flux, etc...) so by setting the grid_mode of the reference grid to 'initialization' we make sure it will be overwritten (as opposed to 'combined') by the running grid at the next update.
 
189
            CALL DS_UPDATE_GRID('Helicity')
 
190
                        CALL DS_SET_GRID_MODE('Helicity','init')
 
191
            call reset_cumulative_variable() ! avoid biais of the initialization
 
192
          endif
 
193
            ELSE
 
194
           JHEL = 1
 
195
           IF(NTRY.LE.MAXTRIES)THEN
 
196
             DO I=1,NCOMB
 
197
                IF (.NOT.GOODHEL(I) .AND. (TS(I).GT.ANS*LIMHEL/NCOMB)) THEN
 
198
                   GOODHEL(I)=.TRUE.
 
199
                   NGOOD = NGOOD +1
 
200
                   IGOOD(NGOOD) = I        
 
201
                   print *,'Adding good helicity ',I,TS(I)/ANS
 
202
                ENDIF
 
203
             ENDDO
 
204
          ENDIF
 
205
          IF(NTRY.EQ.MAXTRIES)THEN
 
206
              ISUM_HEL=MIN(ISUM_HEL,NGOOD)
 
207
          ENDIF
 
208
        IF(NTRY(IMIRROR).EQ.(MAXTRIES+1)) THEN
 
209
           call reset_cumulative_variable() ! avoid biais of the initialization
 
210
        ENDIF
 
211
 
 
212
                endif
 
213
       ELSE              !RANDOM HELICITY
 
214
C           The helicity configuration was chosen already by genps and put in a common block defined in genps.inc.
 
215
            I = HEL_PICKED
 
216
             
 
217
                        CALL %(ml_prefix)sSLOOPMATRIXHEL_THRES(P,I,ANS_ML,-1.0d0,PREC_FOUND,ML_RET_CODE)
 
218
                        T = ANS_ML(1,0)
 
219
            DO JJ=1,JAMP2(0)
 
220
              JAMP2(JJ) = JAMP2(JJ) + ML_JAMP2(JJ)
 
221
            ENDDO
 
222
            DO JJ=1,NLOOPDIAGRAMS
 
223
              AMP2(JJ) = AMP2(JJ)+ ML_AMP2(JJ)
 
224
            ENDDO
 
225
 
 
226
                     DO JJ=1,nincoming
 
227
                IF(POL(JJ).NE.1d0.AND.NHEL(JJ,I).EQ.INT(SIGN(1d0,POL(JJ)))) THEN
 
228
                  T=T*ABS(POL(JJ))
 
229
                ELSE IF(POL(JJ).NE.1d0)THEN
 
230
                  T=T*(2d0-ABS(POL(JJ)))
 
231
                ENDIF
 
232
             ENDDO
 
233
c           Always one helicity at a time
 
234
            ANS = T
 
235
c           Include the Jacobian from helicity sampling
 
236
            ANS = ANS * hel_jacobian 
 
237
                         WRITE(HEL_BUFF,'(20i5)')(NHEL(II,I),II=1,NEXTERNAL)
 
238
       ENDIF
 
239
       IF (ISUM_HEL .NE. 1.or.(HEL_PICKED.eq.-1)) THEN
 
240
          R=XRAN1(IDUM)*ANS
 
241
          SUMHEL=0d0
 
242
          DO I=1,NCOMB
 
243
            SUMHEL=SUMHEL+DABS(TS(I))
 
244
            IF(R.LT.SUMHEL)THEN
 
245
               WRITE(HEL_BUFF,'(20i5)')(NHEL(II,I),II=1,NEXTERNAL)
 
246
               ANS=DSIGN(ANS,TS(i))
 
247
              GOTO 10
 
248
            ENDIF
 
249
          ENDDO
 
250
 10       CONTINUE   
 
251
       ENDIF
 
252
    ENDIF
 
253
 
 
254
   IF (MULTI_CHANNEL) THEN
 
255
        XTOT=0D0
 
256
        DO I=1,NLOOPDIAGRAMS
 
257
            XTOT=XTOT+AMP2(I)
 
258
        ENDDO
 
259
        IF (XTOT.NE.0D0) THEN
 
260
%(set_amp2_line)s
 
261
        ELSE
 
262
            ANS=0D0
 
263
        ENDIF
 
264
    ENDIF
 
265
    IF(.not.Force_ML_Helicity_Sum )THEN
 
266
      ANS = ANS/ Hel_Average_Factor                     
 
267
    ENDIF
 
268
 
 
269
C Amplitude(s) for diagram number %(n_tot_diags)d
 
270
C This last line is a tag do not remove it. 
 
271
    END
 
272
 
 
273