~maddevelopers/mg5amcnlo/2.9.4

« back to all changes in this revision

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

pass to v2.0.0

Show diffs side-by-side

added added

removed removed

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