~maddevelopers/mg5amcnlo/new_clustering

« back to all changes in this revision

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

  • Committer: Rikkert Frederix
  • Date: 2021-09-09 15:51:40 UTC
  • mfrom: (78.75.502 3.2.1)
  • Revision ID: frederix@physik.uzh.ch-20210909155140-rg6umfq68h6h47cf
merge with 3.2.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
      SUBROUTINE SB_SF_%(iborn)3.3d(P1,ANS)
2
 
C  
3
 
%(info_lines)s
4
 
C
5
 
C RETURNS AMPLITUDE SQUARED SUMMED/AVG OVER COLORS
6
 
C AND HELICITIES
7
 
C FOR THE POINT IN PHASE SPACE P(0:3,NEXTERNAL-1)
8
 
C  
9
 
%(process_lines)s
10
 
C
11
 
      IMPLICIT NONE
12
 
C  
13
 
C CONSTANTS
14
 
C  
15
 
      Include "nexternal.inc"
16
 
      INTEGER     NCOMB
17
 
      PARAMETER ( NCOMB=  %(ncomb)d )
18
 
      INTEGER    THEL
19
 
      PARAMETER (THEL=NCOMB*%(nconfs)d)
20
 
      INTEGER NGRAPHS
21
 
      PARAMETER (NGRAPHS=   %(ngraphs)d)
22
 
C  
23
 
C ARGUMENTS 
24
 
C  
25
 
      REAL*8 P1(0:3,NEXTERNAL-1),ANS
26
 
C  
27
 
C LOCAL VARIABLES 
28
 
C  
29
 
      INTEGER IHEL,IDEN,j
30
 
      REAL*8 B_SF_%(iborn)3.3d
31
 
%(den_factor_lines)s
32
 
C  
33
 
C GLOBAL VARIABLES
34
 
C  
35
 
      LOGICAL GOODHEL(NCOMB,%(nconfs)d)
36
 
      common /c_goodhel/ goodhel
37
 
      double precision savemom(nexternal-1,2)
38
 
      common/to_savemom/savemom
39
 
      logical calculatedBorn
40
 
      common/ccalculatedBorn/calculatedBorn
41
 
      integer nfksprocess
42
 
      common/c_nfksprocess/nfksprocess
43
 
C ----------
44
 
C BEGIN CODE
45
 
C ----------
46
 
      iden=iden_values(nfksprocess)
47
 
      if (calculatedBorn) then
48
 
         do j=1,nexternal-1
49
 
            if (savemom(j,1).ne.p1(0,j) .or. savemom(j,2).ne.p1(3,j)) then
50
 
               calculatedBorn=.false.
51
 
               write(*,*) 'Error in sb_sf: momenta not the same in the born'
52
 
               stop
53
 
            endif
54
 
         enddo
55
 
      else
56
 
         write(*,*) 'Error in sb_sf: color_linked borns should be called only with calculatedborn = true'
57
 
         stop
58
 
      endif
59
 
      ANS = 0D0
60
 
      DO IHEL=1,NCOMB
61
 
         IF (GOODHEL(IHEL,nFKSprocess)) THEN
62
 
           ANS=ANS+B_SF_%(iborn)3.3d(P1,IHEL)
63
 
         ENDIF
64
 
      ENDDO
65
 
      ANS=ANS/DBLE(IDEN)
66
 
      END
67
 
       
68
 
       
69
 
      REAL*8 FUNCTION B_SF_%(iborn)3.3d(P,HELL)
70
 
C  
71
 
%(info_lines)s
72
 
C RETURNS AMPLITUDE SQUARED SUMMED/AVG OVER COLORS
73
 
C FOR THE POINT WITH EXTERNAL LINES W(0:6,NEXTERNAL-1)
74
 
 
75
 
%(process_lines)s
76
 
C  
77
 
      IMPLICIT NONE
78
 
C  
79
 
C CONSTANTS
80
 
C  
81
 
      INTEGER     NGRAPHS
82
 
      PARAMETER ( NGRAPHS = %(ngraphs)d ) 
83
 
      INTEGER NCOLOR1, NCOLOR2
84
 
      PARAMETER (NCOLOR1=%(ncolor1)d, NCOLOR2=%(ncolor2)d) 
85
 
      REAL*8     ZERO
86
 
      PARAMETER (ZERO=0D0)
87
 
      complex*16 imag1
88
 
      parameter (imag1 = (0d0,1d0))
89
 
      include "nexternal.inc"
90
 
      include "born_nhel.inc"
91
 
C  
92
 
C ARGUMENTS 
93
 
C  
94
 
      REAL*8 P(0:3,NEXTERNAL-1)
95
 
      INTEGER HELL
96
 
C  
97
 
C LOCAL VARIABLES 
98
 
C  
99
 
      INTEGER I,J
100
 
      REAL*8 DENOM(NCOLOR1), CF(NCOLOR2,NCOLOR1)
101
 
      COMPLEX*16 ZTEMP, AMP(NGRAPHS), JAMP1(NCOLOR1), JAMP2(NCOLOR2)
102
 
C  
103
 
C GLOBAL VARIABLES
104
 
C  
105
 
      double complex saveamp(ngraphs,max_bhel)
106
 
      common/to_saveamp/saveamp
107
 
      logical calculatedBorn
108
 
      common/ccalculatedBorn/calculatedBorn
109
 
C  
110
 
C COLOR DATA
111
 
C  
112
 
%(color_data_lines)s
113
 
C ----------
114
 
C BEGIN CODE
115
 
C ----------
116
 
      if (.not. calculatedBorn) then
117
 
        write(*,*) 'Error in b_sf: color_linked borns should be called only with calculatedborn = true'
118
 
        stop
119
 
      elseif (calculatedBorn) then
120
 
      do i=1,ngraphs
121
 
         amp(i)=saveamp(i,hell)
122
 
      enddo
123
 
      endif
124
 
  %(jamp1_lines)s
125
 
  %(jamp2_lines)s
126
 
      B_SF_%(iborn)3.3d = 0.D0 
127
 
      DO I = 1, NCOLOR1
128
 
          ZTEMP = (0.D0,0.D0)
129
 
          DO J = 1, NCOLOR2
130
 
              ZTEMP = ZTEMP + CF(j,i)*JAMP2(J)
131
 
          ENDDO
132
 
          B_SF_%(iborn)3.3d =B_SF_%(iborn)3.3d+ZTEMP*DCONJG(JAMP1(I))/DENOM(I)   
133
 
      ENDDO
134
 
      END
135
 
       
136