C++InterfacetoTauola
CCX.f
1 c corrected I3 I4: -1 3 -> SDX, -3 1 -> DSX on 5.12.2015
2 C --------- begin processes initiated by CCbar
3 
4  SUBROUTINE ccx(P,I3,I4,H1,H2,KEY,ANS)
5  IMPLICIT NONE
6 
7  INTEGER i3,i4, h1,h2, key
8  REAL*8 p(0:3,6), ans, ans1,ans2,ans3,ans4, ans5,ans6
9 
10  REAL*8 pp(0:3,6)
11 
12 C I3=0,1,2,3 OR 4 I4=0,-1,-2,-3, OR -4
13 C or I3=21 AND I4=21 -> GLUONS AS FINAL JETS
14 
15  ans=0.d0
16 
17  ! switch 4-vectors for I3, I4 and provide/(add contribution from) new configuration
18  pp(0:3,1) = p(0:3,1)
19  pp(0:3,2) = p(0:3,2)
20  pp(0:3,5) = p(0:3,5)
21  pp(0:3,6) = p(0:3,6)
22 
23  pp(0:3,3) = p(0:3,4)
24  pp(0:3,4) = p(0:3,3)
25 
26  IF(key.EQ.1) THEN
27  IF(i3.EQ.1 .AND. i4.EQ.-1) CALL ccx_ddx_h(p,h1,h2,ans)
28  IF(i3.EQ.2 .AND. i4.EQ.-2) CALL ccx_uux_h(p,h1,h2,ans)
29  IF(i3.EQ.3 .AND. i4.EQ.-3) CAll ccx_ssx_h(p,h1,h2,ans)
30  IF(i3.EQ.4 .AND. i4.EQ.-4) CALL ccx_ccx_h(p,h1,h2,ans)
31  IF(i3.EQ.1 .AND. i4.EQ.-3) CALL ccx_dsx_h(p,h1,h2,ans)
32  IF(i3.EQ.3 .AND. i4.EQ.-1) CALL ccx_sdx_h(p,h1,h2,ans)
33  IF(i3.EQ.-1 .AND. i4.EQ.1) CALL ccx_ddx_h(pp,h1,h2,ans)
34  IF(i3.EQ.-2 .AND. i4.EQ.2) CALL ccx_uux_h(pp,h1,h2,ans)
35  IF(i3.EQ.-3 .AND. i4.EQ.3) CAll ccx_ssx_h(pp,h1,h2,ans)
36  IF(i3.EQ.-4 .AND. i4.EQ.4) CALL ccx_ccx_h(pp,h1,h2,ans)
37  IF(i3.EQ.-3 .AND. i4.EQ.1) CALL ccx_dsx_h(pp,h1,h2,ans)
38  IF(i3.EQ.-1 .AND. i4.EQ.3) CALL ccx_sdx_h(pp,h1,h2,ans)
39  IF(i3.EQ.0 .AND. i4.EQ.0) THEN
40  CALL ccx_ddx_h(p,h1,h2,ans1)
41  CALL ccx_uux_h(p,h1,h2,ans2)
42  CALL ccx_ssx_h(p,h1,h2,ans3)
43  CALL ccx_ccx_h(p,h1,h2,ans4)
44  CALL ccx_dsx_h(p,h1,h2,ans5)
45  CALL ccx_sdx_h(p,h1,h2,ans6)
46  ans=ans1+ans2+ans3+ans4+ans5+ans6
47  CALL ccx_ddx_h(pp,h1,h2,ans1)
48  CALL ccx_uux_h(pp,h1,h2,ans2)
49  CALL ccx_ssx_h(pp,h1,h2,ans3)
50  CALL ccx_ccx_h(pp,h1,h2,ans4)
51  CALL ccx_dsx_h(pp,h1,h2,ans5)
52  CALL ccx_sdx_h(pp,h1,h2,ans6)
53  ans=ans1+ans2+ans3+ans4+ans5+ans6+ans
54  ENDIF
55  ELSE IF(key.EQ.0) THEN
56  IF(i3.EQ.1 .AND. i4.EQ.-1) CALL ccx_ddx_noh(p,h1,h2,ans)
57  IF(i3.EQ.2 .AND. i4.EQ.-2) CALL ccx_uux_noh(p,h1,h2,ans)
58  IF(i3.EQ.3 .AND. i4.EQ.-3) CAll ccx_ssx_noh(p,h1,h2,ans)
59  IF(i3.EQ.4 .AND. i4.EQ.-4) CALL ccx_ccx_noh(p,h1,h2,ans)
60  IF(i3.EQ.1 .AND. i4.EQ.-3) CALL ccx_dsx_noh(p,h1,h2,ans)
61  IF(i3.EQ.3 .AND. i4.EQ.-1) CALL ccx_sdx_noh(p,h1,h2,ans)
62  IF(i3.EQ.-1 .AND. i4.EQ.1) CALL ccx_ddx_noh(pp,h1,h2,ans)
63  IF(i3.EQ.-2 .AND. i4.EQ.2) CALL ccx_uux_noh(pp,h1,h2,ans)
64  IF(i3.EQ.-3 .AND. i4.EQ.3) CAll ccx_ssx_noh(pp,h1,h2,ans)
65  IF(i3.EQ.-4 .AND. i4.EQ.4) CALL ccx_ccx_noh(pp,h1,h2,ans)
66  IF(i3.EQ.-3 .AND. i4.EQ.1) CALL ccx_dsx_noh(pp,h1,h2,ans)
67  IF(i3.EQ.-1 .AND. i4.EQ.3) CALL ccx_sdx_noh(pp,h1,h2,ans)
68  IF(i3.EQ.21 .AND. i4.EQ.21) CALL ccx_gg_noh(p,h1,h2,ans)
69  IF(i3.EQ.0 .AND. i4.EQ.0) THEN
70  CALL ccx_ddx_noh(p,h1,h2,ans1)
71  CALL ccx_uux_noh(p,h1,h2,ans2)
72  CALL ccx_ssx_noh(p,h1,h2,ans3)
73  CALL ccx_ccx_noh(p,h1,h2,ans4)
74  CALL ccx_dsx_noh(p,h1,h2,ans5)
75  CALL ccx_sdx_noh(p,h1,h2,ans6)
76  ans=ans1+ans2+ans3+ans4+ans5+ans6
77  CALL ccx_ddx_noh(pp,h1,h2,ans1)
78  CALL ccx_uux_noh(pp,h1,h2,ans2)
79  CALL ccx_ssx_noh(pp,h1,h2,ans3)
80  CALL ccx_ccx_noh(pp,h1,h2,ans4)
81  CALL ccx_dsx_noh(pp,h1,h2,ans5)
82  CALL ccx_sdx_noh(pp,h1,h2,ans6)
83  ans=ans1+ans2+ans3+ans4+ans5+ans6+ans
84  CALL ccx_gg_noh(p,h1,h2,ans1)
85  ans=ans1+ans
86  ENDIF
87  ELSE
88  WRITE(*,*) 'NOT FINISHED'
89  stop
90  ENDIF
91  END ! SUBROUTINE CCX
92 
93 
94 
95 C ----- begin subprocesses CCX->DDX with Higgs->tautau
96 
97  SUBROUTINE ccx_ddx_h(P,H1,H2,ANS)
98 
99 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
100 C By the MadGraph Development Team
101 C Please visit us at https://launchpad.net/madgraph5
102 C
103 C MadGraph StandAlone Version
104 C
105 C Returns amplitude squared summed/avg over colors
106 C and helicities
107 C for the point in phase space P(0:3,NEXTERNAL)
108 C
109 C Process: c c~ > d d~ h WEIGHTED=6
110 C * Decay: h > ta+ ta- WEIGHTED=2
111 C
112  IMPLICIT NONE
113 C
114 C CONSTANTS
115 C
116  INTEGER nexternal
117  parameter(nexternal=6)
118  INTEGER ncomb
119  parameter( ncomb=64)
120 C
121 C ARGUMENTS
122 C
123  REAL*8 p(0:3,nexternal),ans
124  INTEGER h1,h2
125 C
126 C LOCAL VARIABLES
127 C
128  INTEGER nhel(nexternal,ncomb),ntry
129  REAL*8 t
130  REAL*8 matrix_ccx_ddx_h
131  INTEGER ihel,iden, i
132  INTEGER jc(nexternal)
133  LOGICAL goodhel(ncomb)
134  DATA ntry/0/
135  DATA goodhel/ncomb*.false./
136  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
137  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
138  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
139  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
140  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
141  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
142  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
143  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
144  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
145  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
146  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
147  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
148  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
149  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
150  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
151  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
152  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
153  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
154  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
155  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
156  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
157  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
158  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
159  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
160  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
161  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
162  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
163  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
164  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
165  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
166  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
167  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
168  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
169  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
170  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
171  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
172  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
173  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
174  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
175  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
176  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
177  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
178  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
179  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
180  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
181  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
182  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
183  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
184  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
185  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
186  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
187  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
188  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
189  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
190  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
191  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
192  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
193  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
194  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
195  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
196  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
197  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
198  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
199  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
200  DATA iden/36/
201 C ----------
202 C BEGIN CODE
203 C ----------
204  DO ihel=1,nexternal
205  jc(ihel) = +1
206  ENDDO
207  ans = 0d0
208  DO ihel=1,ncomb
209  t=matrix_ccx_ddx_h(p ,h1,h2,nhel(1,ihel),jc(1))
210  ans=ans+t
211  ENDDO
212  ans=ans/dble(iden)
213  END
214 
215 
216  REAL*8 FUNCTION matrix_ccx_ddx_h(P,H1,H2,NHEL,IC)
217 C
218 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
219 C By the MadGraph Development Team
220 C Please visit us at https://launchpad.net/madgraph5
221 C
222 C Returns amplitude squared summed/avg over colors
223 C for the point with external lines W(0:6,NEXTERNAL)
224 C
225 C Process: c c~ > d d~ h WEIGHTED=6
226 C * Decay: h > ta+ ta- WEIGHTED=2
227 C
228  IMPLICIT NONE
229 C
230 C CONSTANTS
231 C
232  INTEGER ngraphs
233  parameter(ngraphs=2)
234  INTEGER nexternal
235  parameter(nexternal=6)
236  INTEGER nwavefuncs, ncolor
237  parameter(nwavefuncs=7, ncolor=2)
238  REAL*8 zero
239  parameter(zero=0d0)
240  COMPLEX*16 imag1
241  parameter(imag1=(0d0,1d0))
242 C
243 C ARGUMENTS
244 C
245  REAL*8 p(0:3,nexternal)
246  INTEGER nhel(nexternal), ic(nexternal)
247 C
248 C LOCAL VARIABLES
249 C
250  INTEGER i,j
251  COMPLEX*16 ztemp
252  REAL*8 denom(ncolor), cf(ncolor,ncolor)
253  COMPLEX*16 amp(ngraphs), jamp(ncolor)
254  COMPLEX*16 w(18,nwavefuncs)
255  COMPLEX*16 dum0,dum1
256  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
257 C
258 C GLOBAL VARIABLES
259 C
260  include 'coupl.inc'
261 C
262 C COLOR DATA
263 C
264  DATA denom(1)/1/
265  DATA (cf(i, 1),i= 1, 2) / 9, 3/
266 C 1 T(2,1) T(3,4)
267  DATA denom(2)/1/
268  DATA (cf(i, 2),i= 1, 2) / 3, 9/
269 C 1 T(2,4) T(3,1)
270 
271  INTEGER h1,h2
272  REAL*8 matrix
273  matrix_ccx_ddx_h=0d0
274  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
275  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
276 C ----------
277 C BEGIN CODE
278 C ----------
279  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
280  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
281  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
282  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
283  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
284  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
285  CALL ffs4_3(w(1,5),w(1,6),gc_99,mh,wh,w(1,7))
286  CALL ffv2_5_3(w(1,1),w(1,2),gc_51,gc_58,mz,wz,w(1,6))
287  CALL ffv2_3_3(w(1,4),w(1,3),gc_50,gc_58,mz,wz,w(1,5))
288 C Amplitude(s) for diagram number 1
289  CALL vvs1_0(w(1,6),w(1,5),w(1,7),gc_81,amp(1))
290  CALL ffv2_3(w(1,1),w(1,3),gc_44,mw,ww,w(1,5))
291  CALL ffv2_3(w(1,4),w(1,2),gc_44,mw,ww,w(1,3))
292 C Amplitude(s) for diagram number 2
293  CALL vvs1_0(w(1,5),w(1,3),w(1,7),gc_72,amp(2))
294  jamp(1)=-amp(1)
295  jamp(2)=+amp(2)
296 
297  matrix = 0.d0
298  DO i = 1, ncolor
299  ztemp = (0.d0,0.d0)
300  DO j = 1, ncolor
301  ztemp = ztemp + cf(j,i)*jamp(j)
302  ENDDO
303  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
304  ENDDO
305  matrix_ccx_ddx_h=matrix
306  ENDIF
307  ENDIF
308  END
309 
310 
311 
312 
313 C ----- begin subprocesses CCX->CCX with Higgs->tautau
314 
315  SUBROUTINE ccx_ccx_h(P,H1,H2,ANS)
316 C
317 C
318 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
319 C By the MadGraph Development Team
320 C Please visit us at https://launchpad.net/madgraph5
321 C
322 C MadGraph StandAlone Version
323 C
324 C Returns amplitude squared summed/avg over colors
325 C and helicities
326 C for the point in phase space P(0:3,NEXTERNAL)
327 C
328 C Process: c c~ > c c~ h WEIGHTED=6
329 C * Decay: h > ta+ ta- WEIGHTED=2
330 C
331  IMPLICIT NONE
332 C
333 C CONSTANTS
334 C
335  INTEGER nexternal
336  parameter(nexternal=6)
337  INTEGER ncomb
338  parameter( ncomb=64)
339 C
340 C ARGUMENTS
341 C
342  REAL*8 p(0:3,nexternal),ans
343  INTEGER h1,h2
344 C
345 C LOCAL VARIABLES
346 C
347  INTEGER nhel(nexternal,ncomb),ntry
348  REAL*8 t
349  REAL*8 matrix_ccx_ccx_h
350  INTEGER ihel,iden, i
351  INTEGER jc(nexternal)
352  LOGICAL goodhel(ncomb)
353  DATA ntry/0/
354  DATA goodhel/ncomb*.false./
355  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
356  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
357  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
358  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
359  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
360  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
361  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
362  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
363  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
364  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
365  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
366  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
367  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
368  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
369  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
370  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
371  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
372  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
373  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
374  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
375  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
376  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
377  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
378  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
379  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
380  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
381  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
382  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
383  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
384  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
385  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
386  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
387  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
388  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
389  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
390  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
391  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
392  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
393  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
394  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
395  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
396  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
397  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
398  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
399  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
400  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
401  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
402  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
403  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
404  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
405  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
406  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
407  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
408  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
409  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
410  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
411  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
412  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
413  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
414  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
415  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
416  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
417  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
418  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
419  DATA iden/36/
420 C ----------
421 C BEGIN CODE
422 C ----------
423 
424  DO ihel=1,nexternal
425  jc(ihel) = +1
426  ENDDO
427  ans = 0d0
428  DO ihel=1,ncomb
429  t=matrix_ccx_ccx_h(p ,h1,h2,nhel(1,ihel),jc(1))
430  ans=ans+t
431  ENDDO
432  ans=ans/dble(iden)
433  END
434 
435 
436  REAL*8 FUNCTION matrix_ccx_ccx_h(P,H1,H2,NHEL,IC)
437 C
438 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
439 C By the MadGraph Development Team
440 C Please visit us at https://launchpad.net/madgraph5
441 C
442 C Returns amplitude squared summed/avg over colors
443 C for the point with external lines W(0:6,NEXTERNAL)
444 C
445 C Process: c c~ > c c~ h WEIGHTED=6
446 C * Decay: h > ta+ ta- WEIGHTED=2
447 C
448  IMPLICIT NONE
449 C
450 C CONSTANTS
451 C
452  INTEGER ngraphs
453  parameter(ngraphs=2)
454  INTEGER nexternal
455  parameter(nexternal=6)
456  INTEGER nwavefuncs, ncolor
457  parameter(nwavefuncs=7, ncolor=2)
458  REAL*8 zero
459  parameter(zero=0d0)
460  COMPLEX*16 imag1
461  parameter(imag1=(0d0,1d0))
462 C
463 C ARGUMENTS
464 C
465  REAL*8 p(0:3,nexternal)
466  INTEGER nhel(nexternal), ic(nexternal)
467 C
468 C LOCAL VARIABLES
469 C
470  INTEGER i,j
471  COMPLEX*16 ztemp
472  REAL*8 denom(ncolor), cf(ncolor,ncolor)
473  COMPLEX*16 amp(ngraphs), jamp(ncolor)
474  COMPLEX*16 w(18,nwavefuncs)
475  COMPLEX*16 dum0,dum1
476  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
477 C
478 C GLOBAL VARIABLES
479 C
480  include 'coupl.inc'
481 C
482 C COLOR DATA
483 C
484  DATA denom(1)/1/
485  DATA (cf(i, 1),i= 1, 2) / 9, 3/
486 C 1 T(2,1) T(3,4)
487  DATA denom(2)/1/
488  DATA (cf(i, 2),i= 1, 2) / 3, 9/
489 C 1 T(2,4) T(3,1)
490 
491  INTEGER h1,h2
492  REAL*8 matrix
493  matrix_ccx_ccx_h=0d0
494  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
495  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
496 C ----------
497 C BEGIN CODE
498 C ----------
499  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
500  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
501  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
502  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
503  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
504  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
505  CALL ffs4_3(w(1,5),w(1,6),gc_99,mh,wh,w(1,7))
506  CALL ffv2_5_3(w(1,1),w(1,2),gc_51,gc_58,mz,wz,w(1,6))
507  CALL ffv2_5_3(w(1,4),w(1,3),gc_51,gc_58,mz,wz,w(1,5))
508 C Amplitude(s) for diagram number 1
509  CALL vvs1_0(w(1,6),w(1,5),w(1,7),gc_81,amp(1))
510  CALL ffv2_5_3(w(1,1),w(1,3),gc_51,gc_58,mz,wz,w(1,5))
511  CALL ffv2_5_3(w(1,4),w(1,2),gc_51,gc_58,mz,wz,w(1,3))
512 C Amplitude(s) for diagram number 2
513  CALL vvs1_0(w(1,5),w(1,3),w(1,7),gc_81,amp(2))
514  jamp(1)=-amp(1)
515  jamp(2)=+amp(2)
516 
517  matrix = 0.d0
518  DO i = 1, ncolor
519  ztemp = (0.d0,0.d0)
520  DO j = 1, ncolor
521  ztemp = ztemp + cf(j,i)*jamp(j)
522  ENDDO
523  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
524  ENDDO
525  matrix_ccx_ccx_h=matrix
526  ENDIF
527  ENDIF
528  END
529 
530 
531 
532 
533 C ----- begin subprocesses CCX->SSX with Higgs->tautau
534 
535  SUBROUTINE ccx_ssx_h(P,H1,H2,ANS)
536 C
537 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
538 C By the MadGraph Development Team
539 C Please visit us at https://launchpad.net/madgraph5
540 C
541 C MadGraph StandAlone Version
542 C
543 C Returns amplitude squared summed/avg over colors
544 C and helicities
545 C for the point in phase space P(0:3,NEXTERNAL)
546 C
547 C Process: c c~ > s s~ h WEIGHTED=6
548 C * Decay: h > ta+ ta- WEIGHTED=2
549 C
550  IMPLICIT NONE
551 C
552 C CONSTANTS
553 C
554  INTEGER nexternal
555  parameter(nexternal=6)
556  INTEGER ncomb
557  parameter( ncomb=64)
558 C
559 C ARGUMENTS
560 C
561  REAL*8 p(0:3,nexternal),ans
562  INTEGER h1,h2
563 C
564 C LOCAL VARIABLES
565 C
566  INTEGER nhel(nexternal,ncomb),ntry
567  REAL*8 t
568  REAL*8 matrix_ccx_ssx_h
569  INTEGER ihel,iden, i
570  INTEGER jc(nexternal)
571  LOGICAL goodhel(ncomb)
572  DATA ntry/0/
573  DATA goodhel/ncomb*.false./
574  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
575  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
576  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
577  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
578  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
579  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
580  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
581  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
582  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
583  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
584  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
585  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
586  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
587  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
588  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
589  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
590  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
591  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
592  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
593  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
594  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
595  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
596  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
597  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
598  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
599  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
600  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
601  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
602  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
603  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
604  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
605  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
606  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
607  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
608  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
609  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
610  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
611  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
612  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
613  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
614  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
615  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
616  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
617  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
618  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
619  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
620  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
621  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
622  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
623  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
624  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
625  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
626  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
627  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
628  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
629  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
630  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
631  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
632  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
633  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
634  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
635  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
636  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
637  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
638  DATA iden/36/
639 C ----------
640 C BEGIN CODE
641 C ----------
642  DO ihel=1,nexternal
643  jc(ihel) = +1
644  ENDDO
645  ans = 0d0
646  DO ihel=1,ncomb
647  t=matrix_ccx_ssx_h(p ,h1,h2,nhel(1,ihel),jc(1))
648  ans=ans+t
649  ENDDO
650  ans=ans/dble(iden)
651  END
652 
653 
654  REAL*8 FUNCTION matrix_ccx_ssx_h(P,H1,H2,NHEL,IC)
655 C
656 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
657 C By the MadGraph Development Team
658 C Please visit us at https://launchpad.net/madgraph5
659 C
660 C Returns amplitude squared summed/avg over colors
661 C for the point with external lines W(0:6,NEXTERNAL)
662 C
663 C Process: c c~ > s s~ h WEIGHTED=6
664 C * Decay: h > ta+ ta- WEIGHTED=2
665 C
666  IMPLICIT NONE
667 C
668 C CONSTANTS
669 C
670  INTEGER ngraphs
671  parameter(ngraphs=2)
672  INTEGER nexternal
673  parameter(nexternal=6)
674  INTEGER nwavefuncs, ncolor
675  parameter(nwavefuncs=7, ncolor=2)
676  REAL*8 zero
677  parameter(zero=0d0)
678  COMPLEX*16 imag1
679  parameter(imag1=(0d0,1d0))
680 C
681 C ARGUMENTS
682 C
683  REAL*8 p(0:3,nexternal)
684  INTEGER nhel(nexternal), ic(nexternal)
685 C
686 C LOCAL VARIABLES
687 C
688  INTEGER i,j
689  COMPLEX*16 ztemp
690  REAL*8 denom(ncolor), cf(ncolor,ncolor)
691  COMPLEX*16 amp(ngraphs), jamp(ncolor)
692  COMPLEX*16 w(18,nwavefuncs)
693  COMPLEX*16 dum0,dum1
694  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
695 C
696 C GLOBAL VARIABLES
697 C
698  include 'coupl.inc'
699 C
700 C COLOR DATA
701 C
702  DATA denom(1)/1/
703  DATA (cf(i, 1),i= 1, 2) / 9, 3/
704 C 1 T(2,1) T(3,4)
705  DATA denom(2)/1/
706  DATA (cf(i, 2),i= 1, 2) / 3, 9/
707 C 1 T(2,4) T(3,1)
708  INTEGER h1,h2
709  REAL*8 matrix
710  matrix_ccx_ssx_h=0d0
711  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
712  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
713 C ----------
714 C BEGIN CODE
715 C ----------
716  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
717  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
718  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
719  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
720  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
721  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
722  CALL ffs4_3(w(1,5),w(1,6),gc_99,mh,wh,w(1,7))
723  CALL ffv2_5_3(w(1,1),w(1,2),gc_51,gc_58,mz,wz,w(1,6))
724  CALL ffv2_3_3(w(1,4),w(1,3),gc_50,gc_58,mz,wz,w(1,5))
725 C Amplitude(s) for diagram number 1
726  CALL vvs1_0(w(1,6),w(1,5),w(1,7),gc_81,amp(1))
727  CALL ffv2_3(w(1,1),w(1,3),gc_100,mw,ww,w(1,5))
728  CALL ffv2_3(w(1,4),w(1,2),gc_100,mw,ww,w(1,3))
729 C Amplitude(s) for diagram number 2
730  CALL vvs1_0(w(1,5),w(1,3),w(1,7),gc_72,amp(2))
731  jamp(1)=-amp(1)
732  jamp(2)=+amp(2)
733 
734  matrix = 0.d0
735  DO i = 1, ncolor
736  ztemp = (0.d0,0.d0)
737  DO j = 1, ncolor
738  ztemp = ztemp + cf(j,i)*jamp(j)
739  ENDDO
740  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
741  ENDDO
742  matrix_ccx_ssx_h=matrix
743  ENDIF
744  ENDIF
745  END
746 
747 
748 
749 
750 
751 
752 C ----- begin subprocesses CCX->UUX with Higgs->tautau
753 
754  SUBROUTINE ccx_uux_h(P,H1,H2,ANS)
755 C
756 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
757 C By the MadGraph Development Team
758 C Please visit us at https://launchpad.net/madgraph5
759 C
760 C MadGraph StandAlone Version
761 C
762 C Returns amplitude squared summed/avg over colors
763 C and helicities
764 C for the point in phase space P(0:3,NEXTERNAL)
765 C
766 C Process: c c~ > u u~ h WEIGHTED=6
767 C * Decay: h > ta+ ta- WEIGHTED=2
768 C
769  IMPLICIT NONE
770 C
771 C CONSTANTS
772 C
773  INTEGER nexternal
774  parameter(nexternal=6)
775  INTEGER ncomb
776  parameter( ncomb=64)
777 C
778 C ARGUMENTS
779 C
780  REAL*8 p(0:3,nexternal),ans
781  INTEGER h1,h2
782 C
783 C LOCAL VARIABLES
784 C
785  INTEGER nhel(nexternal,ncomb),ntry
786  REAL*8 t
787  REAL*8 matrix_ccx_uux_h
788  INTEGER ihel,iden, i
789  INTEGER jc(nexternal)
790  LOGICAL goodhel(ncomb)
791  DATA ntry/0/
792  DATA goodhel/ncomb*.false./
793  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
794  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
795  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
796  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
797  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
798  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
799  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
800  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
801  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
802  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
803  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
804  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
805  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
806  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
807  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
808  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
809  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
810  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
811  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
812  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
813  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
814  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
815  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
816  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
817  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
818  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
819  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
820  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
821  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
822  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
823  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
824  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
825  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
826  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
827  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
828  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
829  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
830  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
831  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
832  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
833  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
834  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
835  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
836  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
837  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
838  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
839  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
840  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
841  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
842  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
843  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
844  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
845  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
846  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
847  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
848  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
849  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
850  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
851  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
852  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
853  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
854  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
855  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
856  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
857  DATA iden/36/
858 C ----------
859 C BEGIN CODE
860 C ----------
861  DO ihel=1,nexternal
862  jc(ihel) = +1
863  ENDDO
864  ans = 0d0
865  DO ihel=1,ncomb
866  t=matrix_ccx_uux_h(p ,h1,h2,nhel(1,ihel),jc(1))
867  ans=ans+t
868  ENDDO
869  ans=ans/dble(iden)
870  END
871 
872 
873  REAL*8 FUNCTION matrix_ccx_uux_h(P,H1,H2,NHEL,IC)
874 C
875 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
876 C By the MadGraph Development Team
877 C Please visit us at https://launchpad.net/madgraph5
878 C
879 C Returns amplitude squared summed/avg over colors
880 C for the point with external lines W(0:6,NEXTERNAL)
881 C
882 C Process: c c~ > u u~ h WEIGHTED=6
883 C * Decay: h > ta+ ta- WEIGHTED=2
884 C
885  IMPLICIT NONE
886 C
887 C CONSTANTS
888 C
889  INTEGER ngraphs
890  parameter(ngraphs=1)
891  INTEGER nexternal
892  parameter(nexternal=6)
893  INTEGER nwavefuncs, ncolor
894  parameter(nwavefuncs=7, ncolor=1)
895  REAL*8 zero
896  parameter(zero=0d0)
897  COMPLEX*16 imag1
898  parameter(imag1=(0d0,1d0))
899 C
900 C ARGUMENTS
901 C
902  REAL*8 p(0:3,nexternal)
903  INTEGER nhel(nexternal), ic(nexternal)
904 C
905 C LOCAL VARIABLES
906 C
907  INTEGER i,j
908  COMPLEX*16 ztemp
909  REAL*8 denom(ncolor), cf(ncolor,ncolor)
910  COMPLEX*16 amp(ngraphs), jamp(ncolor)
911  COMPLEX*16 w(18,nwavefuncs)
912  COMPLEX*16 dum0,dum1
913  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
914 C
915 C GLOBAL VARIABLES
916 C
917  include 'coupl.inc'
918 C
919 C COLOR DATA
920 C
921  DATA denom(1)/1/
922  DATA (cf(i, 1),i= 1, 1) / 9/
923 C 1 T(2,1) T(3,4)
924 
925  INTEGER h1,h2
926  REAL*8 matrix
927  matrix_ccx_uux_h=0d0
928  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
929  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
930 
931 C ----------
932 C BEGIN CODE
933 C ----------
934  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
935  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
936  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
937  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
938  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
939  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
940  CALL ffs4_3(w(1,5),w(1,6),gc_99,mh,wh,w(1,7))
941  CALL ffv2_5_3(w(1,1),w(1,2),gc_51,gc_58,mz,wz,w(1,6))
942  CALL ffv2_5_3(w(1,4),w(1,3),gc_51,gc_58,mz,wz,w(1,2))
943 C Amplitude(s) for diagram number 1
944  CALL vvs1_0(w(1,6),w(1,2),w(1,7),gc_81,amp(1))
945  jamp(1)=-amp(1)
946 
947  matrix = 0.d0
948  DO i = 1, ncolor
949  ztemp = (0.d0,0.d0)
950  DO j = 1, ncolor
951  ztemp = ztemp + cf(j,i)*jamp(j)
952  ENDDO
953  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
954  ENDDO
955  matrix_ccx_uux_h=matrix
956  ENDIF
957  ENDIF
958  END
959 
960 
961 
962 C ----- begin subprocesses CCX->DSX with Higgs->tautau
963 
964  SUBROUTINE ccx_dsx_h(P,H1,H2,ANS)
965 C
966 C
967 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
968 C By the MadGraph Development Team
969 C Please visit us at https://launchpad.net/madgraph5
970 C
971 C MadGraph StandAlone Version
972 C
973 C Returns amplitude squared summed/avg over colors
974 C and helicities
975 C for the point in phase space P(0:3,NEXTERNAL)
976 C
977 C Process: c c~ > d s~ h WEIGHTED=6
978 C * Decay: h > ta+ ta- WEIGHTED=2
979 C
980  IMPLICIT NONE
981 C
982 C CONSTANTS
983 C
984  INTEGER nexternal
985  parameter(nexternal=6)
986  INTEGER ncomb
987  parameter( ncomb=64)
988 C
989 C ARGUMENTS
990 C
991  REAL*8 p(0:3,nexternal),ans
992  INTEGER h1,h2
993 C
994 C LOCAL VARIABLES
995 C
996  INTEGER nhel(nexternal,ncomb),ntry
997  REAL*8 t
998  REAL*8 matrix_ccx_dsx_h
999  INTEGER ihel,iden, i
1000  INTEGER jc(nexternal)
1001  LOGICAL goodhel(ncomb)
1002  DATA ntry/0/
1003  DATA goodhel/ncomb*.false./
1004  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
1005  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
1006  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
1007  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
1008  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
1009  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
1010  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
1011  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
1012  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
1013  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
1014  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
1015  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
1016  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
1017  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
1018  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
1019  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
1020  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
1021  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
1022  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
1023  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
1024  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
1025  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
1026  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
1027  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
1028  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
1029  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
1030  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
1031  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
1032  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
1033  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
1034  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
1035  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
1036  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
1037  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
1038  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
1039  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
1040  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
1041  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
1042  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
1043  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
1044  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
1045  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
1046  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
1047  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
1048  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
1049  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
1050  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
1051  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
1052  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
1053  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
1054  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
1055  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
1056  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
1057  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
1058  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
1059  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
1060  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
1061  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
1062  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
1063  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
1064  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
1065  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
1066  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
1067  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
1068  DATA iden/36/
1069 C ----------
1070 C BEGIN CODE
1071 C ----------
1072  DO ihel=1,nexternal
1073  jc(ihel) = +1
1074  ENDDO
1075  ans = 0d0
1076  DO ihel=1,ncomb
1077  t=matrix_ccx_dsx_h(p ,h1,h2,nhel(1,ihel),jc(1))
1078  ans=ans+t
1079  ENDDO
1080  ans=ans/dble(iden)
1081  END
1082 
1083 
1084  REAL*8 FUNCTION matrix_ccx_dsx_h(P,H1,H2,NHEL,IC)
1085 C
1086 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
1087 C By the MadGraph Development Team
1088 C Please visit us at https://launchpad.net/madgraph5
1089 C
1090 C Returns amplitude squared summed/avg over colors
1091 C for the point with external lines W(0:6,NEXTERNAL)
1092 C
1093 C Process: c c~ > d s~ h WEIGHTED=6
1094 C * Decay: h > ta+ ta- WEIGHTED=2
1095 C
1096  IMPLICIT NONE
1097 C
1098 C CONSTANTS
1099 C
1100  INTEGER ngraphs
1101  parameter(ngraphs=1)
1102  INTEGER nexternal
1103  parameter(nexternal=6)
1104  INTEGER nwavefuncs, ncolor
1105  parameter(nwavefuncs=7, ncolor=1)
1106  REAL*8 zero
1107  parameter(zero=0d0)
1108  COMPLEX*16 imag1
1109  parameter(imag1=(0d0,1d0))
1110 C
1111 C ARGUMENTS
1112 C
1113  REAL*8 p(0:3,nexternal)
1114  INTEGER nhel(nexternal), ic(nexternal)
1115 C
1116 C LOCAL VARIABLES
1117 C
1118  INTEGER i,j
1119  COMPLEX*16 ztemp
1120  REAL*8 denom(ncolor), cf(ncolor,ncolor)
1121  COMPLEX*16 amp(ngraphs), jamp(ncolor)
1122  COMPLEX*16 w(18,nwavefuncs)
1123  COMPLEX*16 dum0,dum1
1124  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
1125 C
1126 C GLOBAL VARIABLES
1127 C
1128  include 'coupl.inc'
1129 C
1130 C COLOR DATA
1131 C
1132  DATA denom(1)/1/
1133  DATA (cf(i, 1),i= 1, 1) / 9/
1134 C 1 T(2,4) T(3,1)
1135 
1136  INTEGER h1,h2
1137  REAL*8 matrix
1138  matrix_ccx_dsx_h=0d0
1139  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
1140  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
1141 
1142 C ----------
1143 C BEGIN CODE
1144 C ----------
1145  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
1146  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
1147  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
1148  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
1149  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
1150  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
1151  CALL ffs4_3(w(1,5),w(1,6),gc_99,mh,wh,w(1,7))
1152  CALL ffv2_3(w(1,1),w(1,3),gc_44,mw,ww,w(1,6))
1153  CALL ffv2_3(w(1,4),w(1,2),gc_100,mw,ww,w(1,3))
1154 C Amplitude(s) for diagram number 1
1155  CALL vvs1_0(w(1,6),w(1,3),w(1,7),gc_72,amp(1))
1156  jamp(1)=+amp(1)
1157 
1158  matrix = 0.d0
1159  DO i = 1, ncolor
1160  ztemp = (0.d0,0.d0)
1161  DO j = 1, ncolor
1162  ztemp = ztemp + cf(j,i)*jamp(j)
1163  ENDDO
1164  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
1165  ENDDO
1166  matrix_ccx_dsx_h=matrix
1167  ENDIF
1168  ENDIF
1169  END
1170 
1171 
1172 
1173 C ------- BEFFINING SUBPROCESS CCX->SDX with H->tautau
1174 
1175  SUBROUTINE ccx_sdx_h(P,H1,H2,ANS)
1176 C
1177 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
1178 C By the MadGraph Development Team
1179 C Please visit us at https://launchpad.net/madgraph5
1180 C
1181 C MadGraph StandAlone Version
1182 C
1183 C Returns amplitude squared summed/avg over colors
1184 C and helicities
1185 C for the point in phase space P(0:3,NEXTERNAL)
1186 C
1187 C Process: c c~ > s d~ h WEIGHTED=6
1188 C * Decay: h > ta+ ta- WEIGHTED=2
1189 C
1190  IMPLICIT NONE
1191 C
1192 C CONSTANTS
1193 C
1194  INTEGER nexternal
1195  parameter(nexternal=6)
1196  INTEGER ncomb
1197  parameter( ncomb=64)
1198 C
1199 C ARGUMENTS
1200 C
1201  REAL*8 p(0:3,nexternal),ans
1202  INTEGER h1,h2
1203 C
1204 C LOCAL VARIABLES
1205 C
1206  INTEGER nhel(nexternal,ncomb),ntry
1207  REAL*8 t
1208  REAL*8 matrix_ccx_sdx_h
1209  INTEGER ihel,iden, i
1210  INTEGER jc(nexternal)
1211  LOGICAL goodhel(ncomb)
1212  DATA ntry/0/
1213  DATA goodhel/ncomb*.false./
1214  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
1215  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
1216  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
1217  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
1218  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
1219  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
1220  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
1221  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
1222  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
1223  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
1224  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
1225  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
1226  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
1227  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
1228  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
1229  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
1230  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
1231  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
1232  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
1233  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
1234  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
1235  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
1236  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
1237  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
1238  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
1239  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
1240  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
1241  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
1242  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
1243  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
1244  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
1245  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
1246  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
1247  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
1248  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
1249  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
1250  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
1251  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
1252  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
1253  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
1254  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
1255  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
1256  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
1257  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
1258  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
1259  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
1260  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
1261  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
1262  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
1263  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
1264  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
1265  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
1266  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
1267  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
1268  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
1269  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
1270  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
1271  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
1272  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
1273  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
1274  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
1275  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
1276  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
1277  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
1278  DATA iden/36/
1279 C ----------
1280 C BEGIN CODE
1281 C ----------
1282  DO ihel=1,nexternal
1283  jc(ihel) = +1
1284  ENDDO
1285  ans = 0d0
1286  DO ihel=1,ncomb
1287  t=matrix_ccx_sdx_h(p ,h1,h2,nhel(1,ihel),jc(1))
1288  ans=ans+t
1289  ENDDO
1290  ans=ans/dble(iden)
1291  END
1292 
1293 
1294  REAL*8 FUNCTION matrix_ccx_sdx_h(P,H1,H2,NHEL,IC)
1295 C
1296 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
1297 C By the MadGraph Development Team
1298 C Please visit us at https://launchpad.net/madgraph5
1299 C
1300 C Returns amplitude squared summed/avg over colors
1301 C for the point with external lines W(0:6,NEXTERNAL)
1302 C
1303 C Process: c c~ > s d~ h WEIGHTED=6
1304 C * Decay: h > ta+ ta- WEIGHTED=2
1305 C
1306  IMPLICIT NONE
1307 C
1308 C CONSTANTS
1309 C
1310  INTEGER ngraphs
1311  parameter(ngraphs=1)
1312  INTEGER nexternal
1313  parameter(nexternal=6)
1314  INTEGER nwavefuncs, ncolor
1315  parameter(nwavefuncs=7, ncolor=1)
1316  REAL*8 zero
1317  parameter(zero=0d0)
1318  COMPLEX*16 imag1
1319  parameter(imag1=(0d0,1d0))
1320 C
1321 C ARGUMENTS
1322 C
1323  REAL*8 p(0:3,nexternal)
1324  INTEGER nhel(nexternal), ic(nexternal)
1325 C
1326 C LOCAL VARIABLES
1327 C
1328  INTEGER i,j
1329  COMPLEX*16 ztemp
1330  REAL*8 denom(ncolor), cf(ncolor,ncolor)
1331  COMPLEX*16 amp(ngraphs), jamp(ncolor)
1332  COMPLEX*16 w(18,nwavefuncs)
1333  COMPLEX*16 dum0,dum1
1334  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
1335 C
1336 C GLOBAL VARIABLES
1337 C
1338  include 'coupl.inc'
1339 C
1340 C COLOR DATA
1341 C
1342  DATA denom(1)/1/
1343  DATA (cf(i, 1),i= 1, 1) / 9/
1344 C 1 T(2,4) T(3,1)
1345 
1346  INTEGER h1,h2
1347  REAL*8 matrix
1348  matrix_ccx_sdx_h=0d0
1349  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
1350  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
1351 
1352 C ----------
1353 C BEGIN CODE
1354 C ----------
1355  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
1356  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
1357  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
1358  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
1359  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
1360  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
1361  CALL ffs4_3(w(1,5),w(1,6),gc_99,mh,wh,w(1,7))
1362  CALL ffv2_3(w(1,1),w(1,3),gc_100,mw,ww,w(1,6))
1363  CALL ffv2_3(w(1,4),w(1,2),gc_44,mw,ww,w(1,3))
1364 C Amplitude(s) for diagram number 1
1365  CALL vvs1_0(w(1,6),w(1,3),w(1,7),gc_72,amp(1))
1366  jamp(1)=+amp(1)
1367 
1368  matrix = 0.d0
1369  DO i = 1, ncolor
1370  ztemp = (0.d0,0.d0)
1371  DO j = 1, ncolor
1372  ztemp = ztemp + cf(j,i)*jamp(j)
1373  ENDDO
1374  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
1375  ENDDO
1376  matrix_ccx_sdx_h=matrix
1377  ENDIF
1378  ENDIF
1379  END
1380 
1381 
1382 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
1383 C ----- begin subprocesses ud->jjtautau, no Higgs
1384 
1385 C-----------SUBPROCESS CCX->DDX NO HIGGS
1386 
1387  SUBROUTINE ccx_ddx_noh(P,H1,H2,ANS)
1388 C
1389 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
1390 C By the MadGraph Development Team
1391 C Please visit us at https://launchpad.net/madgraph5
1392 C
1393 C MadGraph StandAlone Version
1394 C
1395 C Returns amplitude squared summed/avg over colors
1396 C and helicities
1397 C for the point in phase space P(0:3,NEXTERNAL)
1398 C
1399 C Process: c c~ > d d~ ta+ ta- / h Qed=4
1400 C
1401  IMPLICIT NONE
1402 C
1403 C CONSTANTS
1404 C
1405  INTEGER nexternal
1406  parameter(nexternal=6)
1407  INTEGER ncomb
1408  parameter( ncomb=64)
1409 C
1410 C ARGUMENTS
1411 C
1412  REAL*8 p(0:3,nexternal),ans
1413  INTEGER h1,h2
1414 C
1415 C LOCAL VARIABLES
1416 C
1417  INTEGER nhel(nexternal,ncomb),ntry
1418  REAL*8 t
1419  REAL*8 matrix_ccx_ddx_noh
1420  INTEGER ihel,iden, i
1421  INTEGER jc(nexternal)
1422  LOGICAL goodhel(ncomb)
1423  DATA ntry/0/
1424  DATA goodhel/ncomb*.false./
1425  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
1426  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
1427  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
1428  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
1429  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
1430  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
1431  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
1432  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
1433  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
1434  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
1435  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
1436  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
1437  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
1438  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
1439  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
1440  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
1441  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
1442  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
1443  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
1444  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
1445  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
1446  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
1447  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
1448  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
1449  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
1450  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
1451  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
1452  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
1453  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
1454  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
1455  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
1456  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
1457  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
1458  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
1459  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
1460  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
1461  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
1462  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
1463  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
1464  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
1465  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
1466  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
1467  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
1468  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
1469  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
1470  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
1471  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
1472  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
1473  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
1474  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
1475  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
1476  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
1477  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
1478  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
1479  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
1480  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
1481  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
1482  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
1483  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
1484  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
1485  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
1486  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
1487  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
1488  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
1489  DATA iden/36/
1490 C ----------
1491 C BEGIN CODE
1492 C ----------
1493  DO ihel=1,nexternal
1494  jc(ihel) = +1
1495  ENDDO
1496  ans = 0d0
1497  DO ihel=1,ncomb
1498  t=matrix_ccx_ddx_noh(p ,h1,h2,nhel(1,ihel),jc(1))
1499  ans=ans+t
1500  ENDDO
1501  ans=ans/dble(iden)
1502  END
1503 
1504  REAL*8 FUNCTION matrix_ccx_ddx_noh(P,H1,H2,NHEL,IC)
1505 C
1506 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
1507 C By the MadGraph Development Team
1508 C Please visit us at https://launchpad.net/madgraph5
1509 C
1510 C Returns amplitude squared summed/avg over colors
1511 C for the point with external lines W(0:6,NEXTERNAL)
1512 C
1513 C Process: c c~ > d d~ ta+ ta- / h Qed=4
1514 C
1515  IMPLICIT NONE
1516 C
1517 C CONSTANTS
1518 C
1519  INTEGER ngraphs
1520  parameter(ngraphs=43)
1521  INTEGER nexternal
1522  parameter(nexternal=6)
1523  INTEGER nwavefuncs, ncolor
1524  parameter(nwavefuncs=14, ncolor=2)
1525  REAL*8 zero
1526  parameter(zero=0d0)
1527  COMPLEX*16 imag1
1528  parameter(imag1=(0d0,1d0))
1529 C
1530 C ARGUMENTS
1531 C
1532  REAL*8 p(0:3,nexternal)
1533  INTEGER nhel(nexternal), ic(nexternal)
1534 C
1535 C LOCAL VARIABLES
1536 C
1537  INTEGER i,j
1538  COMPLEX*16 ztemp
1539  REAL*8 denom(ncolor), cf(ncolor,ncolor)
1540  COMPLEX*16 amp(ngraphs), jamp(ncolor)
1541  COMPLEX*16 w(18,nwavefuncs)
1542  COMPLEX*16 dum0,dum1
1543  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
1544 C
1545 C GLOBAL VARIABLES
1546 C
1547  include 'coupl.inc'
1548 C
1549 C COLOR DATA
1550 C
1551  DATA denom(1)/1/
1552  DATA (cf(i, 1),i= 1, 2) / 9, 3/
1553 C 1 T(2,1) T(3,4)
1554  DATA denom(2)/1/
1555  DATA (cf(i, 2),i= 1, 2) / 3, 9/
1556 C 1 T(2,4) T(3,1)
1557 
1558  INTEGER h1,h2
1559  REAL*8 matrix
1560  matrix_ccx_ddx_noh=0d0
1561  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
1562  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
1563 
1564 C ----------
1565 C BEGIN CODE
1566 C ----------
1567  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
1568  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
1569  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
1570  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
1571  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
1572  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
1573  CALL ffv1p0_3(w(1,1),w(1,2),gc_2,zero,zero,w(1,7))
1574  CALL ffv1p0_3(w(1,4),w(1,3),gc_1,zero,zero,w(1,8))
1575  CALL ffv1_2(w(1,5),w(1,7),gc_3,mta,zero,w(1,9))
1576 C Amplitude(s) for diagram number 1
1577  CALL ffv1_0(w(1,9),w(1,6),w(1,8),gc_3,amp(1))
1578  CALL ffv1_1(w(1,6),w(1,7),gc_3,mta,zero,w(1,10))
1579 C Amplitude(s) for diagram number 2
1580  CALL ffv1_0(w(1,5),w(1,10),w(1,8),gc_3,amp(2))
1581  CALL ffv2_3_3(w(1,4),w(1,3),gc_50,gc_58,mz,wz,w(1,11))
1582 C Amplitude(s) for diagram number 3
1583  CALL ffv2_4_0(w(1,9),w(1,6),w(1,11),gc_50,gc_59,amp(3))
1584 C Amplitude(s) for diagram number 4
1585  CALL ffv2_4_0(w(1,5),w(1,10),w(1,11),gc_50,gc_59,amp(4))
1586  CALL ffv2_5_3(w(1,1),w(1,2),gc_51,gc_58,mz,wz,w(1,10))
1587  CALL ffv2_4_2(w(1,5),w(1,10),gc_50,gc_59,mta,zero,w(1,9))
1588 C Amplitude(s) for diagram number 5
1589  CALL ffv1_0(w(1,9),w(1,6),w(1,8),gc_3,amp(5))
1590  CALL ffv2_4_1(w(1,6),w(1,10),gc_50,gc_59,mta,zero,w(1,12))
1591 C Amplitude(s) for diagram number 6
1592  CALL ffv1_0(w(1,5),w(1,12),w(1,8),gc_3,amp(6))
1593 C Amplitude(s) for diagram number 7
1594  CALL ffv2_4_0(w(1,9),w(1,6),w(1,11),gc_50,gc_59,amp(7))
1595 C Amplitude(s) for diagram number 8
1596  CALL ffv2_4_0(w(1,5),w(1,12),w(1,11),gc_50,gc_59,amp(8))
1597  CALL ffv1p0_3(w(1,5),w(1,6),gc_3,zero,zero,w(1,12))
1598  CALL ffv1_1(w(1,3),w(1,7),gc_1,zero,zero,w(1,9))
1599 C Amplitude(s) for diagram number 9
1600  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_1,amp(9))
1601  CALL ffv1_2(w(1,4),w(1,7),gc_1,zero,zero,w(1,13))
1602 C Amplitude(s) for diagram number 10
1603  CALL ffv1_0(w(1,13),w(1,3),w(1,12),gc_1,amp(10))
1604  CALL ffv2_4_3(w(1,5),w(1,6),gc_50,gc_59,mz,wz,w(1,7))
1605 C Amplitude(s) for diagram number 11
1606  CALL ffv2_3_0(w(1,4),w(1,9),w(1,7),gc_50,gc_58,amp(11))
1607 C Amplitude(s) for diagram number 12
1608  CALL ffv2_3_0(w(1,13),w(1,3),w(1,7),gc_50,gc_58,amp(12))
1609  CALL ffv1p0_3(w(1,1),w(1,2),gc_11,zero,zero,w(1,13))
1610  CALL ffv1_1(w(1,3),w(1,13),gc_11,zero,zero,w(1,9))
1611 C Amplitude(s) for diagram number 13
1612  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_1,amp(13))
1613  CALL ffv1_2(w(1,4),w(1,13),gc_11,zero,zero,w(1,14))
1614 C Amplitude(s) for diagram number 14
1615  CALL ffv1_0(w(1,14),w(1,3),w(1,12),gc_1,amp(14))
1616 C Amplitude(s) for diagram number 15
1617  CALL ffv2_3_0(w(1,4),w(1,9),w(1,7),gc_50,gc_58,amp(15))
1618 C Amplitude(s) for diagram number 16
1619  CALL ffv2_3_0(w(1,14),w(1,3),w(1,7),gc_50,gc_58,amp(16))
1620  CALL ffv2_3_1(w(1,3),w(1,10),gc_50,gc_58,zero,zero,w(1,14))
1621 C Amplitude(s) for diagram number 17
1622  CALL ffv1_0(w(1,4),w(1,14),w(1,12),gc_1,amp(17))
1623  CALL ffv2_3_2(w(1,4),w(1,10),gc_50,gc_58,zero,zero,w(1,9))
1624 C Amplitude(s) for diagram number 18
1625  CALL ffv1_0(w(1,9),w(1,3),w(1,12),gc_1,amp(18))
1626 C Amplitude(s) for diagram number 19
1627  CALL ffv2_3_0(w(1,4),w(1,14),w(1,7),gc_50,gc_58,amp(19))
1628 C Amplitude(s) for diagram number 20
1629  CALL ffv2_3_0(w(1,9),w(1,3),w(1,7),gc_50,gc_58,amp(20))
1630  CALL ffv2_3(w(1,1),w(1,3),gc_44,mw,ww,w(1,9))
1631  CALL ffv2_3(w(1,4),w(1,2),gc_44,mw,ww,w(1,14))
1632  CALL ffv2_2(w(1,5),w(1,9),gc_108,zero,zero,w(1,10))
1633 C Amplitude(s) for diagram number 21
1634  CALL ffv2_0(w(1,10),w(1,6),w(1,14),gc_108,amp(21))
1635 C Amplitude(s) for diagram number 22
1636  CALL vvv1_0(w(1,12),w(1,9),w(1,14),gc_4,amp(22))
1637 C Amplitude(s) for diagram number 23
1638  CALL vvv1_0(w(1,9),w(1,14),w(1,7),gc_53,amp(23))
1639  CALL ffv2_1(w(1,2),w(1,9),gc_44,zero,zero,w(1,10))
1640 C Amplitude(s) for diagram number 24
1641  CALL ffv1_0(w(1,4),w(1,10),w(1,12),gc_1,amp(24))
1642  CALL ffv2_2(w(1,4),w(1,9),gc_44,zero,zero,w(1,6))
1643 C Amplitude(s) for diagram number 25
1644  CALL ffv1_0(w(1,6),w(1,2),w(1,12),gc_2,amp(25))
1645 C Amplitude(s) for diagram number 26
1646  CALL ffv2_3_0(w(1,4),w(1,10),w(1,7),gc_50,gc_58,amp(26))
1647 C Amplitude(s) for diagram number 27
1648  CALL ffv2_5_0(w(1,6),w(1,2),w(1,7),gc_51,gc_58,amp(27))
1649  CALL ffv2_2(w(1,1),w(1,14),gc_44,zero,zero,w(1,6))
1650 C Amplitude(s) for diagram number 28
1651  CALL ffv1_0(w(1,6),w(1,3),w(1,12),gc_1,amp(28))
1652  CALL ffv1_2(w(1,1),w(1,12),gc_2,zero,zero,w(1,10))
1653 C Amplitude(s) for diagram number 29
1654  CALL ffv2_0(w(1,10),w(1,3),w(1,14),gc_44,amp(29))
1655 C Amplitude(s) for diagram number 30
1656  CALL ffv2_3_0(w(1,6),w(1,3),w(1,7),gc_50,gc_58,amp(30))
1657  CALL ffv2_5_2(w(1,1),w(1,7),gc_51,gc_58,zero,zero,w(1,6))
1658 C Amplitude(s) for diagram number 31
1659  CALL ffv2_0(w(1,6),w(1,3),w(1,14),gc_44,amp(31))
1660  CALL ffv1_2(w(1,1),w(1,8),gc_2,zero,zero,w(1,14))
1661 C Amplitude(s) for diagram number 32
1662  CALL ffv1_0(w(1,14),w(1,2),w(1,12),gc_2,amp(32))
1663 C Amplitude(s) for diagram number 33
1664  CALL ffv1_0(w(1,10),w(1,2),w(1,8),gc_2,amp(33))
1665 C Amplitude(s) for diagram number 34
1666  CALL ffv2_5_0(w(1,14),w(1,2),w(1,7),gc_51,gc_58,amp(34))
1667 C Amplitude(s) for diagram number 35
1668  CALL ffv1_0(w(1,6),w(1,2),w(1,8),gc_2,amp(35))
1669  CALL ffv1p0_3(w(1,4),w(1,3),gc_11,zero,zero,w(1,8))
1670  CALL ffv1_2(w(1,1),w(1,8),gc_11,zero,zero,w(1,4))
1671 C Amplitude(s) for diagram number 36
1672  CALL ffv1_0(w(1,4),w(1,2),w(1,12),gc_2,amp(36))
1673 C Amplitude(s) for diagram number 37
1674  CALL ffv1_0(w(1,10),w(1,2),w(1,8),gc_11,amp(37))
1675 C Amplitude(s) for diagram number 38
1676  CALL ffv2_5_0(w(1,4),w(1,2),w(1,7),gc_51,gc_58,amp(38))
1677 C Amplitude(s) for diagram number 39
1678  CALL ffv1_0(w(1,6),w(1,2),w(1,8),gc_11,amp(39))
1679  CALL ffv2_5_2(w(1,1),w(1,11),gc_51,gc_58,zero,zero,w(1,8))
1680 C Amplitude(s) for diagram number 40
1681  CALL ffv1_0(w(1,8),w(1,2),w(1,12),gc_2,amp(40))
1682 C Amplitude(s) for diagram number 41
1683  CALL ffv2_5_0(w(1,10),w(1,2),w(1,11),gc_51,gc_58,amp(41))
1684 C Amplitude(s) for diagram number 42
1685  CALL ffv2_5_0(w(1,8),w(1,2),w(1,7),gc_51,gc_58,amp(42))
1686 C Amplitude(s) for diagram number 43
1687  CALL ffv2_5_0(w(1,6),w(1,2),w(1,11),gc_51,gc_58,amp(43))
1688  jamp(1)=-amp(1)-amp(2)-amp(3)-amp(4)-amp(5)-amp(6)-amp(7)-amp(8)
1689  $ -amp(9)-amp(10)-amp(11)-amp(12)+1./6.*amp(13)+1./6.*amp(14)
1690  $ +1./6.*amp(15)+1./6.*amp(16)-amp(17)-amp(18)-amp(19)-amp(20)
1691  $ -amp(32)-amp(33)-amp(34)-amp(35)+1./6.*amp(36)+1./6.*amp(37)
1692  $ +1./6.*amp(38)+1./6.*amp(39)-amp(40)-amp(41)-amp(42)-amp(43)
1693  jamp(2)=-1./2.*amp(13)-1./2.*amp(14)-1./2.*amp(15)-1./2.*amp(16)
1694  $ +amp(21)+amp(22)+amp(23)+amp(24)+amp(25)+amp(26)+amp(27)
1695  $ +amp(28)+amp(29)+amp(30)+amp(31)-1./2.*amp(36)-1./2.*amp(37)
1696  $ -1./2.*amp(38)-1./2.*amp(39)
1697 
1698  matrix = 0.d0
1699  DO i = 1, ncolor
1700  ztemp = (0.d0,0.d0)
1701  DO j = 1, ncolor
1702  ztemp = ztemp + cf(j,i)*jamp(j)
1703  ENDDO
1704  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
1705  ENDDO
1706  matrix_ccx_ddx_noh=matrix
1707  ENDIF
1708  ENDIF
1709  END
1710 
1711 C-----------SUBPROCESS CCX->UUX NO HIGGS
1712 
1713  SUBROUTINE ccx_uux_noh(P,H1,H2,ANS)
1714 C
1715 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
1716 C By the MadGraph Development Team
1717 C Please visit us at https://launchpad.net/madgraph5
1718 C
1719 C MadGraph StandAlone Version
1720 C
1721 C Returns amplitude squared summed/avg over colors
1722 C and helicities
1723 C for the point in phase space P(0:3,NEXTERNAL)
1724 C
1725 C Process: c c~ > u u~ ta+ ta- / h Qed=4
1726 C
1727  IMPLICIT NONE
1728 C
1729 C CONSTANTS
1730 C
1731  INTEGER nexternal
1732  parameter(nexternal=6)
1733  INTEGER ncomb
1734  parameter( ncomb=64)
1735 C
1736 C ARGUMENTS
1737 C
1738  REAL*8 p(0:3,nexternal),ans
1739  INTEGER h1,h2
1740 C
1741 C LOCAL VARIABLES
1742 C
1743  INTEGER nhel(nexternal,ncomb),ntry
1744  REAL*8 t
1745  REAL*8 matrix_ccx_uux_noh
1746  INTEGER ihel,iden, i
1747  INTEGER jc(nexternal)
1748  LOGICAL goodhel(ncomb)
1749  DATA ntry/0/
1750  DATA goodhel/ncomb*.false./
1751  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
1752  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
1753  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
1754  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
1755  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
1756  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
1757  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
1758  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
1759  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
1760  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
1761  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
1762  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
1763  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
1764  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
1765  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
1766  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
1767  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
1768  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
1769  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
1770  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
1771  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
1772  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
1773  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
1774  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
1775  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
1776  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
1777  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
1778  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
1779  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
1780  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
1781  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
1782  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
1783  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
1784  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
1785  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
1786  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
1787  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
1788  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
1789  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
1790  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
1791  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
1792  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
1793  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
1794  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
1795  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
1796  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
1797  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
1798  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
1799  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
1800  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
1801  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
1802  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
1803  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
1804  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
1805  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
1806  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
1807  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
1808  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
1809  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
1810  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
1811  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
1812  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
1813  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
1814  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
1815  DATA iden/36/
1816 C ----------
1817 C BEGIN CODE
1818 C ----------
1819  DO ihel=1,nexternal
1820  jc(ihel) = +1
1821  ENDDO
1822  ans = 0d0
1823  DO ihel=1,ncomb
1824  t=matrix_ccx_uux_noh(p ,h1,h2,nhel(1,ihel),jc(1))
1825  ans=ans+t
1826  ENDDO
1827  ans=ans/dble(iden)
1828  END
1829 
1830 
1831  REAL*8 FUNCTION matrix_ccx_uux_noh(P,H1,H2,NHEL,IC)
1832 C
1833 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
1834 C By the MadGraph Development Team
1835 C Please visit us at https://launchpad.net/madgraph5
1836 C
1837 C Returns amplitude squared summed/avg over colors
1838 C for the point with external lines W(0:6,NEXTERNAL)
1839 C
1840 C Process: c c~ > u u~ ta+ ta- / h Qed=4
1841 C
1842  IMPLICIT NONE
1843 C
1844 C CONSTANTS
1845 C
1846  INTEGER ngraphs
1847  parameter(ngraphs=32)
1848  INTEGER nexternal
1849  parameter(nexternal=6)
1850  INTEGER nwavefuncs, ncolor
1851  parameter(nwavefuncs=13, ncolor=2)
1852  REAL*8 zero
1853  parameter(zero=0d0)
1854  COMPLEX*16 imag1
1855  parameter(imag1=(0d0,1d0))
1856 C
1857 C ARGUMENTS
1858 C
1859  REAL*8 p(0:3,nexternal)
1860  INTEGER nhel(nexternal), ic(nexternal)
1861 C
1862 C LOCAL VARIABLES
1863 C
1864  INTEGER i,j
1865  COMPLEX*16 ztemp
1866  REAL*8 denom(ncolor), cf(ncolor,ncolor)
1867  COMPLEX*16 amp(ngraphs), jamp(ncolor)
1868  COMPLEX*16 w(18,nwavefuncs)
1869  COMPLEX*16 dum0,dum1
1870  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
1871 C
1872 C GLOBAL VARIABLES
1873 C
1874  include 'coupl.inc'
1875 C
1876 C COLOR DATA
1877 C
1878  DATA denom(1)/1/
1879  DATA (cf(i, 1),i= 1, 2) / 9, 3/
1880 C 1 T(2,1) T(3,4)
1881  DATA denom(2)/1/
1882  DATA (cf(i, 2),i= 1, 2) / 3, 9/
1883 C 1 T(2,4) T(3,1)
1884 
1885  INTEGER h1,h2
1886  REAL*8 matrix
1887  matrix_ccx_uux_noh=0d0
1888  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
1889  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
1890 
1891 C ----------
1892 C BEGIN CODE
1893 C ----------
1894  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
1895  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
1896  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
1897  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
1898  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
1899  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
1900  CALL ffv1p0_3(w(1,1),w(1,2),gc_2,zero,zero,w(1,7))
1901  CALL ffv1p0_3(w(1,4),w(1,3),gc_2,zero,zero,w(1,8))
1902  CALL ffv1_2(w(1,5),w(1,7),gc_3,mta,zero,w(1,9))
1903 C Amplitude(s) for diagram number 1
1904  CALL ffv1_0(w(1,9),w(1,6),w(1,8),gc_3,amp(1))
1905  CALL ffv1_1(w(1,6),w(1,7),gc_3,mta,zero,w(1,10))
1906 C Amplitude(s) for diagram number 2
1907  CALL ffv1_0(w(1,5),w(1,10),w(1,8),gc_3,amp(2))
1908  CALL ffv2_5_3(w(1,4),w(1,3),gc_51,gc_58,mz,wz,w(1,11))
1909 C Amplitude(s) for diagram number 3
1910  CALL ffv2_4_0(w(1,9),w(1,6),w(1,11),gc_50,gc_59,amp(3))
1911 C Amplitude(s) for diagram number 4
1912  CALL ffv2_4_0(w(1,5),w(1,10),w(1,11),gc_50,gc_59,amp(4))
1913  CALL ffv2_5_3(w(1,1),w(1,2),gc_51,gc_58,mz,wz,w(1,10))
1914  CALL ffv2_4_2(w(1,5),w(1,10),gc_50,gc_59,mta,zero,w(1,9))
1915 C Amplitude(s) for diagram number 5
1916  CALL ffv1_0(w(1,9),w(1,6),w(1,8),gc_3,amp(5))
1917  CALL ffv2_4_1(w(1,6),w(1,10),gc_50,gc_59,mta,zero,w(1,12))
1918 C Amplitude(s) for diagram number 6
1919  CALL ffv1_0(w(1,5),w(1,12),w(1,8),gc_3,amp(6))
1920 C Amplitude(s) for diagram number 7
1921  CALL ffv2_4_0(w(1,9),w(1,6),w(1,11),gc_50,gc_59,amp(7))
1922 C Amplitude(s) for diagram number 8
1923  CALL ffv2_4_0(w(1,5),w(1,12),w(1,11),gc_50,gc_59,amp(8))
1924  CALL ffv1p0_3(w(1,5),w(1,6),gc_3,zero,zero,w(1,12))
1925  CALL ffv1_1(w(1,3),w(1,7),gc_2,zero,zero,w(1,9))
1926 C Amplitude(s) for diagram number 9
1927  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_2,amp(9))
1928  CALL ffv1_2(w(1,4),w(1,7),gc_2,zero,zero,w(1,13))
1929 C Amplitude(s) for diagram number 10
1930  CALL ffv1_0(w(1,13),w(1,3),w(1,12),gc_2,amp(10))
1931  CALL ffv2_4_3(w(1,5),w(1,6),gc_50,gc_59,mz,wz,w(1,7))
1932 C Amplitude(s) for diagram number 11
1933  CALL ffv2_5_0(w(1,4),w(1,9),w(1,7),gc_51,gc_58,amp(11))
1934 C Amplitude(s) for diagram number 12
1935  CALL ffv2_5_0(w(1,13),w(1,3),w(1,7),gc_51,gc_58,amp(12))
1936  CALL ffv1p0_3(w(1,1),w(1,2),gc_11,zero,zero,w(1,13))
1937  CALL ffv1_1(w(1,3),w(1,13),gc_11,zero,zero,w(1,9))
1938 C Amplitude(s) for diagram number 13
1939  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_2,amp(13))
1940  CALL ffv1_2(w(1,4),w(1,13),gc_11,zero,zero,w(1,6))
1941 C Amplitude(s) for diagram number 14
1942  CALL ffv1_0(w(1,6),w(1,3),w(1,12),gc_2,amp(14))
1943 C Amplitude(s) for diagram number 15
1944  CALL ffv2_5_0(w(1,4),w(1,9),w(1,7),gc_51,gc_58,amp(15))
1945 C Amplitude(s) for diagram number 16
1946  CALL ffv2_5_0(w(1,6),w(1,3),w(1,7),gc_51,gc_58,amp(16))
1947  CALL ffv2_5_1(w(1,3),w(1,10),gc_51,gc_58,zero,zero,w(1,6))
1948 C Amplitude(s) for diagram number 17
1949  CALL ffv1_0(w(1,4),w(1,6),w(1,12),gc_2,amp(17))
1950  CALL ffv2_5_2(w(1,4),w(1,10),gc_51,gc_58,zero,zero,w(1,9))
1951 C Amplitude(s) for diagram number 18
1952  CALL ffv1_0(w(1,9),w(1,3),w(1,12),gc_2,amp(18))
1953 C Amplitude(s) for diagram number 19
1954  CALL ffv2_5_0(w(1,4),w(1,6),w(1,7),gc_51,gc_58,amp(19))
1955 C Amplitude(s) for diagram number 20
1956  CALL ffv2_5_0(w(1,9),w(1,3),w(1,7),gc_51,gc_58,amp(20))
1957  CALL ffv1_2(w(1,1),w(1,8),gc_2,zero,zero,w(1,9))
1958 C Amplitude(s) for diagram number 21
1959  CALL ffv1_0(w(1,9),w(1,2),w(1,12),gc_2,amp(21))
1960  CALL ffv1_2(w(1,1),w(1,12),gc_2,zero,zero,w(1,6))
1961 C Amplitude(s) for diagram number 22
1962  CALL ffv1_0(w(1,6),w(1,2),w(1,8),gc_2,amp(22))
1963 C Amplitude(s) for diagram number 23
1964  CALL ffv2_5_0(w(1,9),w(1,2),w(1,7),gc_51,gc_58,amp(23))
1965  CALL ffv2_5_2(w(1,1),w(1,7),gc_51,gc_58,zero,zero,w(1,9))
1966 C Amplitude(s) for diagram number 24
1967  CALL ffv1_0(w(1,9),w(1,2),w(1,8),gc_2,amp(24))
1968  CALL ffv1p0_3(w(1,4),w(1,3),gc_11,zero,zero,w(1,8))
1969  CALL ffv1_2(w(1,1),w(1,8),gc_11,zero,zero,w(1,4))
1970 C Amplitude(s) for diagram number 25
1971  CALL ffv1_0(w(1,4),w(1,2),w(1,12),gc_2,amp(25))
1972 C Amplitude(s) for diagram number 26
1973  CALL ffv1_0(w(1,6),w(1,2),w(1,8),gc_11,amp(26))
1974 C Amplitude(s) for diagram number 27
1975  CALL ffv2_5_0(w(1,4),w(1,2),w(1,7),gc_51,gc_58,amp(27))
1976 C Amplitude(s) for diagram number 28
1977  CALL ffv1_0(w(1,9),w(1,2),w(1,8),gc_11,amp(28))
1978  CALL ffv2_5_2(w(1,1),w(1,11),gc_51,gc_58,zero,zero,w(1,8))
1979 C Amplitude(s) for diagram number 29
1980  CALL ffv1_0(w(1,8),w(1,2),w(1,12),gc_2,amp(29))
1981 C Amplitude(s) for diagram number 30
1982  CALL ffv2_5_0(w(1,6),w(1,2),w(1,11),gc_51,gc_58,amp(30))
1983 C Amplitude(s) for diagram number 31
1984  CALL ffv2_5_0(w(1,8),w(1,2),w(1,7),gc_51,gc_58,amp(31))
1985 C Amplitude(s) for diagram number 32
1986  CALL ffv2_5_0(w(1,9),w(1,2),w(1,11),gc_51,gc_58,amp(32))
1987  jamp(1)=-amp(1)-amp(2)-amp(3)-amp(4)-amp(5)-amp(6)-amp(7)-amp(8)
1988  $ -amp(9)-amp(10)-amp(11)-amp(12)+1./6.*amp(13)+1./6.*amp(14)
1989  $ +1./6.*amp(15)+1./6.*amp(16)-amp(17)-amp(18)-amp(19)-amp(20)
1990  $ -amp(21)-amp(22)-amp(23)-amp(24)+1./6.*amp(25)+1./6.*amp(26)
1991  $ +1./6.*amp(27)+1./6.*amp(28)-amp(29)-amp(30)-amp(31)-amp(32)
1992  jamp(2)=+1./2.*(-amp(13)-amp(14)-amp(15)-amp(16)-amp(25)-amp(26)
1993  $ -amp(27)-amp(28))
1994 
1995  matrix = 0.d0
1996  DO i = 1, ncolor
1997  ztemp = (0.d0,0.d0)
1998  DO j = 1, ncolor
1999  ztemp = ztemp + cf(j,i)*jamp(j)
2000  ENDDO
2001  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
2002  ENDDO
2003  matrix_ccx_uux_noh=matrix
2004  ENDIF
2005  ENDIF
2006  END
2007 
2008 C-----------SUBPROCESS CCX->SSX NO HIGGS
2009 
2010  SUBROUTINE ccx_ssx_noh(P,H1,H2,ANS)
2011 C
2012 C
2013 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
2014 C By the MadGraph Development Team
2015 C Please visit us at https://launchpad.net/madgraph5
2016 C
2017 C MadGraph StandAlone Version
2018 C
2019 C Returns amplitude squared summed/avg over colors
2020 C and helicities
2021 C for the point in phase space P(0:3,NEXTERNAL)
2022 C
2023 C Process: c c~ > s s~ ta+ ta- / h Qed=4
2024 C
2025  IMPLICIT NONE
2026 C
2027 C CONSTANTS
2028 C
2029  INTEGER nexternal
2030  parameter(nexternal=6)
2031  INTEGER ncomb
2032  parameter( ncomb=64)
2033 C
2034 C ARGUMENTS
2035 C
2036  REAL*8 p(0:3,nexternal),ans
2037  INTEGER h1,h2
2038 C
2039 C LOCAL VARIABLES
2040 C
2041  INTEGER nhel(nexternal,ncomb),ntry
2042  REAL*8 t
2043  REAL*8 matrix_ccx_ssx_noh
2044  INTEGER ihel,iden, i
2045  INTEGER jc(nexternal)
2046  LOGICAL goodhel(ncomb)
2047  DATA ntry/0/
2048  DATA goodhel/ncomb*.false./
2049  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
2050  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
2051  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
2052  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
2053  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
2054  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
2055  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
2056  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
2057  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
2058  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
2059  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
2060  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
2061  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
2062  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
2063  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
2064  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
2065  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
2066  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
2067  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
2068  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
2069  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
2070  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
2071  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
2072  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
2073  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
2074  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
2075  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
2076  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
2077  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
2078  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
2079  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
2080  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
2081  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
2082  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
2083  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
2084  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
2085  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
2086  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
2087  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
2088  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
2089  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
2090  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
2091  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
2092  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
2093  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
2094  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
2095  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
2096  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
2097  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
2098  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
2099  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
2100  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
2101  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
2102  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
2103  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
2104  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
2105  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
2106  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
2107  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
2108  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
2109  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
2110  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
2111  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
2112  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
2113  DATA iden/36/
2114 C ----------
2115 C BEGIN CODE
2116 C ----------
2117  DO ihel=1,nexternal
2118  jc(ihel) = +1
2119  ENDDO
2120  ans = 0d0
2121  DO ihel=1,ncomb
2122  t=matrix_ccx_ssx_noh(p ,h1,h2,nhel(1,ihel),jc(1))
2123  ans=ans+t
2124  ENDDO
2125  ans=ans/dble(iden)
2126  END
2127 
2128 
2129  REAL*8 FUNCTION matrix_ccx_ssx_noh(P,H1,H2,NHEL,IC)
2130 C
2131 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
2132 C By the MadGraph Development Team
2133 C Please visit us at https://launchpad.net/madgraph5
2134 C
2135 C Returns amplitude squared summed/avg over colors
2136 C for the point with external lines W(0:6,NEXTERNAL)
2137 C
2138 C Process: c c~ > s s~ ta+ ta- / h Qed=4
2139 C
2140  IMPLICIT NONE
2141 C
2142 C CONSTANTS
2143 C
2144  INTEGER ngraphs
2145  parameter(ngraphs=43)
2146  INTEGER nexternal
2147  parameter(nexternal=6)
2148  INTEGER nwavefuncs, ncolor
2149  parameter(nwavefuncs=14, ncolor=2)
2150  REAL*8 zero
2151  parameter(zero=0d0)
2152  COMPLEX*16 imag1
2153  parameter(imag1=(0d0,1d0))
2154 C
2155 C ARGUMENTS
2156 C
2157  REAL*8 p(0:3,nexternal)
2158  INTEGER nhel(nexternal), ic(nexternal)
2159 C
2160 C LOCAL VARIABLES
2161 C
2162  INTEGER i,j
2163  COMPLEX*16 ztemp
2164  REAL*8 denom(ncolor), cf(ncolor,ncolor)
2165  COMPLEX*16 amp(ngraphs), jamp(ncolor)
2166  COMPLEX*16 w(18,nwavefuncs)
2167  COMPLEX*16 dum0,dum1
2168  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
2169 C
2170 C GLOBAL VARIABLES
2171 C
2172  include 'coupl.inc'
2173 C
2174 C COLOR DATA
2175 C
2176  DATA denom(1)/1/
2177  DATA (cf(i, 1),i= 1, 2) / 9, 3/
2178 C 1 T(2,1) T(3,4)
2179  DATA denom(2)/1/
2180  DATA (cf(i, 2),i= 1, 2) / 3, 9/
2181 C 1 T(2,4) T(3,1)
2182 
2183  INTEGER h1,h2
2184  REAL*8 matrix
2185  matrix_ccx_ssx_noh=0d0
2186  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
2187  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
2188 
2189 C ----------
2190 C BEGIN CODE
2191 C ----------
2192  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
2193  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
2194  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
2195  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
2196  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
2197  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
2198  CALL ffv1p0_3(w(1,1),w(1,2),gc_2,zero,zero,w(1,7))
2199  CALL ffv1p0_3(w(1,4),w(1,3),gc_1,zero,zero,w(1,8))
2200  CALL ffv1_2(w(1,5),w(1,7),gc_3,mta,zero,w(1,9))
2201 C Amplitude(s) for diagram number 1
2202  CALL ffv1_0(w(1,9),w(1,6),w(1,8),gc_3,amp(1))
2203  CALL ffv1_1(w(1,6),w(1,7),gc_3,mta,zero,w(1,10))
2204 C Amplitude(s) for diagram number 2
2205  CALL ffv1_0(w(1,5),w(1,10),w(1,8),gc_3,amp(2))
2206  CALL ffv2_3_3(w(1,4),w(1,3),gc_50,gc_58,mz,wz,w(1,11))
2207 C Amplitude(s) for diagram number 3
2208  CALL ffv2_4_0(w(1,9),w(1,6),w(1,11),gc_50,gc_59,amp(3))
2209 C Amplitude(s) for diagram number 4
2210  CALL ffv2_4_0(w(1,5),w(1,10),w(1,11),gc_50,gc_59,amp(4))
2211  CALL ffv2_5_3(w(1,1),w(1,2),gc_51,gc_58,mz,wz,w(1,10))
2212  CALL ffv2_4_2(w(1,5),w(1,10),gc_50,gc_59,mta,zero,w(1,9))
2213 C Amplitude(s) for diagram number 5
2214  CALL ffv1_0(w(1,9),w(1,6),w(1,8),gc_3,amp(5))
2215  CALL ffv2_4_1(w(1,6),w(1,10),gc_50,gc_59,mta,zero,w(1,12))
2216 C Amplitude(s) for diagram number 6
2217  CALL ffv1_0(w(1,5),w(1,12),w(1,8),gc_3,amp(6))
2218 C Amplitude(s) for diagram number 7
2219  CALL ffv2_4_0(w(1,9),w(1,6),w(1,11),gc_50,gc_59,amp(7))
2220 C Amplitude(s) for diagram number 8
2221  CALL ffv2_4_0(w(1,5),w(1,12),w(1,11),gc_50,gc_59,amp(8))
2222  CALL ffv1p0_3(w(1,5),w(1,6),gc_3,zero,zero,w(1,12))
2223  CALL ffv1_1(w(1,3),w(1,7),gc_1,zero,zero,w(1,9))
2224 C Amplitude(s) for diagram number 9
2225  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_1,amp(9))
2226  CALL ffv1_2(w(1,4),w(1,7),gc_1,zero,zero,w(1,13))
2227 C Amplitude(s) for diagram number 10
2228  CALL ffv1_0(w(1,13),w(1,3),w(1,12),gc_1,amp(10))
2229  CALL ffv2_4_3(w(1,5),w(1,6),gc_50,gc_59,mz,wz,w(1,7))
2230 C Amplitude(s) for diagram number 11
2231  CALL ffv2_3_0(w(1,4),w(1,9),w(1,7),gc_50,gc_58,amp(11))
2232 C Amplitude(s) for diagram number 12
2233  CALL ffv2_3_0(w(1,13),w(1,3),w(1,7),gc_50,gc_58,amp(12))
2234  CALL ffv1p0_3(w(1,1),w(1,2),gc_11,zero,zero,w(1,13))
2235  CALL ffv1_1(w(1,3),w(1,13),gc_11,zero,zero,w(1,9))
2236 C Amplitude(s) for diagram number 13
2237  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_1,amp(13))
2238  CALL ffv1_2(w(1,4),w(1,13),gc_11,zero,zero,w(1,14))
2239 C Amplitude(s) for diagram number 14
2240  CALL ffv1_0(w(1,14),w(1,3),w(1,12),gc_1,amp(14))
2241 C Amplitude(s) for diagram number 15
2242  CALL ffv2_3_0(w(1,4),w(1,9),w(1,7),gc_50,gc_58,amp(15))
2243 C Amplitude(s) for diagram number 16
2244  CALL ffv2_3_0(w(1,14),w(1,3),w(1,7),gc_50,gc_58,amp(16))
2245  CALL ffv2_3_1(w(1,3),w(1,10),gc_50,gc_58,zero,zero,w(1,14))
2246 C Amplitude(s) for diagram number 17
2247  CALL ffv1_0(w(1,4),w(1,14),w(1,12),gc_1,amp(17))
2248  CALL ffv2_3_2(w(1,4),w(1,10),gc_50,gc_58,zero,zero,w(1,9))
2249 C Amplitude(s) for diagram number 18
2250  CALL ffv1_0(w(1,9),w(1,3),w(1,12),gc_1,amp(18))
2251 C Amplitude(s) for diagram number 19
2252  CALL ffv2_3_0(w(1,4),w(1,14),w(1,7),gc_50,gc_58,amp(19))
2253 C Amplitude(s) for diagram number 20
2254  CALL ffv2_3_0(w(1,9),w(1,3),w(1,7),gc_50,gc_58,amp(20))
2255  CALL ffv2_3(w(1,1),w(1,3),gc_100,mw,ww,w(1,9))
2256  CALL ffv2_3(w(1,4),w(1,2),gc_100,mw,ww,w(1,14))
2257  CALL ffv2_2(w(1,5),w(1,9),gc_108,zero,zero,w(1,10))
2258 C Amplitude(s) for diagram number 21
2259  CALL ffv2_0(w(1,10),w(1,6),w(1,14),gc_108,amp(21))
2260 C Amplitude(s) for diagram number 22
2261  CALL vvv1_0(w(1,12),w(1,9),w(1,14),gc_4,amp(22))
2262 C Amplitude(s) for diagram number 23
2263  CALL vvv1_0(w(1,9),w(1,14),w(1,7),gc_53,amp(23))
2264  CALL ffv2_1(w(1,2),w(1,9),gc_100,zero,zero,w(1,10))
2265 C Amplitude(s) for diagram number 24
2266  CALL ffv1_0(w(1,4),w(1,10),w(1,12),gc_1,amp(24))
2267  CALL ffv2_2(w(1,4),w(1,9),gc_100,zero,zero,w(1,6))
2268 C Amplitude(s) for diagram number 25
2269  CALL ffv1_0(w(1,6),w(1,2),w(1,12),gc_2,amp(25))
2270 C Amplitude(s) for diagram number 26
2271  CALL ffv2_3_0(w(1,4),w(1,10),w(1,7),gc_50,gc_58,amp(26))
2272 C Amplitude(s) for diagram number 27
2273  CALL ffv2_5_0(w(1,6),w(1,2),w(1,7),gc_51,gc_58,amp(27))
2274  CALL ffv2_2(w(1,1),w(1,14),gc_100,zero,zero,w(1,6))
2275 C Amplitude(s) for diagram number 28
2276  CALL ffv1_0(w(1,6),w(1,3),w(1,12),gc_1,amp(28))
2277  CALL ffv1_2(w(1,1),w(1,12),gc_2,zero,zero,w(1,10))
2278 C Amplitude(s) for diagram number 29
2279  CALL ffv2_0(w(1,10),w(1,3),w(1,14),gc_100,amp(29))
2280 C Amplitude(s) for diagram number 30
2281  CALL ffv2_3_0(w(1,6),w(1,3),w(1,7),gc_50,gc_58,amp(30))
2282  CALL ffv2_5_2(w(1,1),w(1,7),gc_51,gc_58,zero,zero,w(1,6))
2283 C Amplitude(s) for diagram number 31
2284  CALL ffv2_0(w(1,6),w(1,3),w(1,14),gc_100,amp(31))
2285  CALL ffv1_2(w(1,1),w(1,8),gc_2,zero,zero,w(1,14))
2286 C Amplitude(s) for diagram number 32
2287  CALL ffv1_0(w(1,14),w(1,2),w(1,12),gc_2,amp(32))
2288 C Amplitude(s) for diagram number 33
2289  CALL ffv1_0(w(1,10),w(1,2),w(1,8),gc_2,amp(33))
2290 C Amplitude(s) for diagram number 34
2291  CALL ffv2_5_0(w(1,14),w(1,2),w(1,7),gc_51,gc_58,amp(34))
2292 C Amplitude(s) for diagram number 35
2293  CALL ffv1_0(w(1,6),w(1,2),w(1,8),gc_2,amp(35))
2294  CALL ffv1p0_3(w(1,4),w(1,3),gc_11,zero,zero,w(1,8))
2295  CALL ffv1_2(w(1,1),w(1,8),gc_11,zero,zero,w(1,4))
2296 C Amplitude(s) for diagram number 36
2297  CALL ffv1_0(w(1,4),w(1,2),w(1,12),gc_2,amp(36))
2298 C Amplitude(s) for diagram number 37
2299  CALL ffv1_0(w(1,10),w(1,2),w(1,8),gc_11,amp(37))
2300 C Amplitude(s) for diagram number 38
2301  CALL ffv2_5_0(w(1,4),w(1,2),w(1,7),gc_51,gc_58,amp(38))
2302 C Amplitude(s) for diagram number 39
2303  CALL ffv1_0(w(1,6),w(1,2),w(1,8),gc_11,amp(39))
2304  CALL ffv2_5_2(w(1,1),w(1,11),gc_51,gc_58,zero,zero,w(1,8))
2305 C Amplitude(s) for diagram number 40
2306  CALL ffv1_0(w(1,8),w(1,2),w(1,12),gc_2,amp(40))
2307 C Amplitude(s) for diagram number 41
2308  CALL ffv2_5_0(w(1,10),w(1,2),w(1,11),gc_51,gc_58,amp(41))
2309 C Amplitude(s) for diagram number 42
2310  CALL ffv2_5_0(w(1,8),w(1,2),w(1,7),gc_51,gc_58,amp(42))
2311 C Amplitude(s) for diagram number 43
2312  CALL ffv2_5_0(w(1,6),w(1,2),w(1,11),gc_51,gc_58,amp(43))
2313  jamp(1)=-amp(1)-amp(2)-amp(3)-amp(4)-amp(5)-amp(6)-amp(7)-amp(8)
2314  $ -amp(9)-amp(10)-amp(11)-amp(12)+1./6.*amp(13)+1./6.*amp(14)
2315  $ +1./6.*amp(15)+1./6.*amp(16)-amp(17)-amp(18)-amp(19)-amp(20)
2316  $ -amp(32)-amp(33)-amp(34)-amp(35)+1./6.*amp(36)+1./6.*amp(37)
2317  $ +1./6.*amp(38)+1./6.*amp(39)-amp(40)-amp(41)-amp(42)-amp(43)
2318  jamp(2)=-1./2.*amp(13)-1./2.*amp(14)-1./2.*amp(15)-1./2.*amp(16)
2319  $ +amp(21)+amp(22)+amp(23)+amp(24)+amp(25)+amp(26)+amp(27)
2320  $ +amp(28)+amp(29)+amp(30)+amp(31)-1./2.*amp(36)-1./2.*amp(37)
2321  $ -1./2.*amp(38)-1./2.*amp(39)
2322 
2323  matrix = 0.d0
2324  DO i = 1, ncolor
2325  ztemp = (0.d0,0.d0)
2326  DO j = 1, ncolor
2327  ztemp = ztemp + cf(j,i)*jamp(j)
2328  ENDDO
2329  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
2330  ENDDO
2331  matrix_ccx_ssx_noh=matrix
2332  ENDIF
2333  ENDIF
2334  END
2335 
2336 C-----------SUBPROCESS CCX->CCX NO HIGGS
2337 
2338  SUBROUTINE ccx_ccx_noh(P,H1,H2,ANS)
2339 C
2340 C
2341 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
2342 C By the MadGraph Development Team
2343 C Please visit us at https://launchpad.net/madgraph5
2344 C
2345 C MadGraph StandAlone Version
2346 C
2347 C Returns amplitude squared summed/avg over colors
2348 C and helicities
2349 C for the point in phase space P(0:3,NEXTERNAL)
2350 C
2351 C Process: c c~ > c c~ ta+ ta- / h Qed=4
2352 C
2353  IMPLICIT NONE
2354 C
2355 C CONSTANTS
2356 C
2357  INTEGER nexternal
2358  parameter(nexternal=6)
2359  INTEGER ncomb
2360  parameter( ncomb=64)
2361 C
2362 C ARGUMENTS
2363 C
2364  REAL*8 p(0:3,nexternal),ans
2365  INTEGER h1,h2
2366 C
2367 C LOCAL VARIABLES
2368 C
2369  INTEGER nhel(nexternal,ncomb),ntry
2370  REAL*8 t
2371  REAL*8 matrix_ccx_ccx_noh
2372  INTEGER ihel,iden, i
2373  INTEGER jc(nexternal)
2374  LOGICAL goodhel(ncomb)
2375  DATA ntry/0/
2376  DATA goodhel/ncomb*.false./
2377  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
2378  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
2379  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
2380  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
2381  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
2382  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
2383  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
2384  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
2385  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
2386  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
2387  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
2388  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
2389  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
2390  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
2391  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
2392  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
2393  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
2394  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
2395  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
2396  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
2397  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
2398  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
2399  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
2400  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
2401  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
2402  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
2403  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
2404  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
2405  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
2406  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
2407  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
2408  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
2409  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
2410  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
2411  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
2412  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
2413  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
2414  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
2415  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
2416  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
2417  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
2418  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
2419  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
2420  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
2421  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
2422  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
2423  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
2424  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
2425  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
2426  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
2427  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
2428  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
2429  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
2430  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
2431  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
2432  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
2433  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
2434  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
2435  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
2436  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
2437  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
2438  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
2439  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
2440  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
2441  DATA iden/36/
2442 C ----------
2443 C BEGIN CODE
2444 C ----------
2445  DO ihel=1,nexternal
2446  jc(ihel) = +1
2447  ENDDO
2448  ans = 0d0
2449  DO ihel=1,ncomb
2450  t=matrix_ccx_ccx_noh(p ,h1,h2,nhel(1,ihel),jc(1))
2451  ans=ans+t
2452  ENDDO
2453  ans=ans/dble(iden)
2454  END
2455 
2456 
2457  REAL*8 FUNCTION matrix_ccx_ccx_noh(P,H1,H2,NHEL,IC)
2458 C
2459 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
2460 C By the MadGraph Development Team
2461 C Please visit us at https://launchpad.net/madgraph5
2462 C
2463 C Returns amplitude squared summed/avg over colors
2464 C for the point with external lines W(0:6,NEXTERNAL)
2465 C
2466 C Process: c c~ > c c~ ta+ ta- / h Qed=4
2467 C
2468  IMPLICIT NONE
2469 C
2470 C CONSTANTS
2471 C
2472  INTEGER ngraphs
2473  parameter(ngraphs=64)
2474  INTEGER nexternal
2475  parameter(nexternal=6)
2476  INTEGER nwavefuncs, ncolor
2477  parameter(nwavefuncs=16, ncolor=2)
2478  REAL*8 zero
2479  parameter(zero=0d0)
2480  COMPLEX*16 imag1
2481  parameter(imag1=(0d0,1d0))
2482 C
2483 C ARGUMENTS
2484 C
2485  REAL*8 p(0:3,nexternal)
2486  INTEGER nhel(nexternal), ic(nexternal)
2487 C
2488 C LOCAL VARIABLES
2489 C
2490  INTEGER i,j
2491  COMPLEX*16 ztemp
2492  REAL*8 denom(ncolor), cf(ncolor,ncolor)
2493  COMPLEX*16 amp(ngraphs), jamp(ncolor)
2494  COMPLEX*16 w(18,nwavefuncs)
2495  COMPLEX*16 dum0,dum1
2496  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
2497 C
2498 C GLOBAL VARIABLES
2499 C
2500  include 'coupl.inc'
2501 C
2502 C COLOR DATA
2503 C
2504  DATA denom(1)/1/
2505  DATA (cf(i, 1),i= 1, 2) / 9, 3/
2506 C 1 T(2,1) T(3,4)
2507  DATA denom(2)/1/
2508  DATA (cf(i, 2),i= 1, 2) / 3, 9/
2509 C 1 T(2,4) T(3,1)
2510 
2511  INTEGER h1,h2
2512  REAL*8 matrix
2513  matrix_ccx_ccx_noh=0d0
2514  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
2515  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
2516 
2517 C ----------
2518 C BEGIN CODE
2519 C ----------
2520  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
2521  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
2522  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
2523  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
2524  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
2525  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
2526  CALL ffv1p0_3(w(1,1),w(1,2),gc_2,zero,zero,w(1,7))
2527  CALL ffv1p0_3(w(1,4),w(1,3),gc_2,zero,zero,w(1,8))
2528  CALL ffv1_2(w(1,5),w(1,7),gc_3,mta,zero,w(1,9))
2529 C Amplitude(s) for diagram number 1
2530  CALL ffv1_0(w(1,9),w(1,6),w(1,8),gc_3,amp(1))
2531  CALL ffv1_1(w(1,6),w(1,7),gc_3,mta,zero,w(1,10))
2532 C Amplitude(s) for diagram number 2
2533  CALL ffv1_0(w(1,5),w(1,10),w(1,8),gc_3,amp(2))
2534  CALL ffv2_5_3(w(1,4),w(1,3),gc_51,gc_58,mz,wz,w(1,11))
2535 C Amplitude(s) for diagram number 3
2536  CALL ffv2_4_0(w(1,9),w(1,6),w(1,11),gc_50,gc_59,amp(3))
2537 C Amplitude(s) for diagram number 4
2538  CALL ffv2_4_0(w(1,5),w(1,10),w(1,11),gc_50,gc_59,amp(4))
2539  CALL ffv2_5_3(w(1,1),w(1,2),gc_51,gc_58,mz,wz,w(1,10))
2540  CALL ffv2_4_2(w(1,5),w(1,10),gc_50,gc_59,mta,zero,w(1,9))
2541 C Amplitude(s) for diagram number 5
2542  CALL ffv1_0(w(1,9),w(1,6),w(1,8),gc_3,amp(5))
2543  CALL ffv2_4_1(w(1,6),w(1,10),gc_50,gc_59,mta,zero,w(1,12))
2544 C Amplitude(s) for diagram number 6
2545  CALL ffv1_0(w(1,5),w(1,12),w(1,8),gc_3,amp(6))
2546 C Amplitude(s) for diagram number 7
2547  CALL ffv2_4_0(w(1,9),w(1,6),w(1,11),gc_50,gc_59,amp(7))
2548 C Amplitude(s) for diagram number 8
2549  CALL ffv2_4_0(w(1,5),w(1,12),w(1,11),gc_50,gc_59,amp(8))
2550  CALL ffv1p0_3(w(1,5),w(1,6),gc_3,zero,zero,w(1,12))
2551  CALL ffv1_1(w(1,3),w(1,7),gc_2,zero,zero,w(1,9))
2552 C Amplitude(s) for diagram number 9
2553  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_2,amp(9))
2554  CALL ffv1_2(w(1,4),w(1,7),gc_2,zero,zero,w(1,13))
2555 C Amplitude(s) for diagram number 10
2556  CALL ffv1_0(w(1,13),w(1,3),w(1,12),gc_2,amp(10))
2557  CALL ffv2_4_3(w(1,5),w(1,6),gc_50,gc_59,mz,wz,w(1,7))
2558 C Amplitude(s) for diagram number 11
2559  CALL ffv2_5_0(w(1,4),w(1,9),w(1,7),gc_51,gc_58,amp(11))
2560 C Amplitude(s) for diagram number 12
2561  CALL ffv2_5_0(w(1,13),w(1,3),w(1,7),gc_51,gc_58,amp(12))
2562  CALL ffv1p0_3(w(1,1),w(1,2),gc_11,zero,zero,w(1,13))
2563  CALL ffv1_1(w(1,3),w(1,13),gc_11,zero,zero,w(1,9))
2564 C Amplitude(s) for diagram number 13
2565  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_2,amp(13))
2566  CALL ffv1_2(w(1,4),w(1,13),gc_11,zero,zero,w(1,14))
2567 C Amplitude(s) for diagram number 14
2568  CALL ffv1_0(w(1,14),w(1,3),w(1,12),gc_2,amp(14))
2569 C Amplitude(s) for diagram number 15
2570  CALL ffv2_5_0(w(1,4),w(1,9),w(1,7),gc_51,gc_58,amp(15))
2571 C Amplitude(s) for diagram number 16
2572  CALL ffv2_5_0(w(1,14),w(1,3),w(1,7),gc_51,gc_58,amp(16))
2573  CALL ffv2_5_1(w(1,3),w(1,10),gc_51,gc_58,zero,zero,w(1,14))
2574 C Amplitude(s) for diagram number 17
2575  CALL ffv1_0(w(1,4),w(1,14),w(1,12),gc_2,amp(17))
2576  CALL ffv2_5_2(w(1,4),w(1,10),gc_51,gc_58,zero,zero,w(1,9))
2577 C Amplitude(s) for diagram number 18
2578  CALL ffv1_0(w(1,9),w(1,3),w(1,12),gc_2,amp(18))
2579 C Amplitude(s) for diagram number 19
2580  CALL ffv2_5_0(w(1,4),w(1,14),w(1,7),gc_51,gc_58,amp(19))
2581 C Amplitude(s) for diagram number 20
2582  CALL ffv2_5_0(w(1,9),w(1,3),w(1,7),gc_51,gc_58,amp(20))
2583  CALL ffv1p0_3(w(1,1),w(1,3),gc_2,zero,zero,w(1,9))
2584  CALL ffv1p0_3(w(1,4),w(1,2),gc_2,zero,zero,w(1,14))
2585  CALL ffv1_2(w(1,5),w(1,9),gc_3,mta,zero,w(1,10))
2586 C Amplitude(s) for diagram number 21
2587  CALL ffv1_0(w(1,10),w(1,6),w(1,14),gc_3,amp(21))
2588  CALL ffv1_1(w(1,6),w(1,9),gc_3,mta,zero,w(1,13))
2589 C Amplitude(s) for diagram number 22
2590  CALL ffv1_0(w(1,5),w(1,13),w(1,14),gc_3,amp(22))
2591  CALL ffv2_5_3(w(1,4),w(1,2),gc_51,gc_58,mz,wz,w(1,15))
2592 C Amplitude(s) for diagram number 23
2593  CALL ffv2_4_0(w(1,10),w(1,6),w(1,15),gc_50,gc_59,amp(23))
2594 C Amplitude(s) for diagram number 24
2595  CALL ffv2_4_0(w(1,5),w(1,13),w(1,15),gc_50,gc_59,amp(24))
2596  CALL ffv2_5_3(w(1,1),w(1,3),gc_51,gc_58,mz,wz,w(1,13))
2597  CALL ffv2_4_2(w(1,5),w(1,13),gc_50,gc_59,mta,zero,w(1,10))
2598 C Amplitude(s) for diagram number 25
2599  CALL ffv1_0(w(1,10),w(1,6),w(1,14),gc_3,amp(25))
2600  CALL ffv2_4_1(w(1,6),w(1,13),gc_50,gc_59,mta,zero,w(1,16))
2601 C Amplitude(s) for diagram number 26
2602  CALL ffv1_0(w(1,5),w(1,16),w(1,14),gc_3,amp(26))
2603 C Amplitude(s) for diagram number 27
2604  CALL ffv2_4_0(w(1,10),w(1,6),w(1,15),gc_50,gc_59,amp(27))
2605 C Amplitude(s) for diagram number 28
2606  CALL ffv2_4_0(w(1,5),w(1,16),w(1,15),gc_50,gc_59,amp(28))
2607  CALL ffv1_1(w(1,2),w(1,9),gc_2,zero,zero,w(1,16))
2608 C Amplitude(s) for diagram number 29
2609  CALL ffv1_0(w(1,4),w(1,16),w(1,12),gc_2,amp(29))
2610  CALL ffv1_2(w(1,4),w(1,9),gc_2,zero,zero,w(1,5))
2611 C Amplitude(s) for diagram number 30
2612  CALL ffv1_0(w(1,5),w(1,2),w(1,12),gc_2,amp(30))
2613 C Amplitude(s) for diagram number 31
2614  CALL ffv2_5_0(w(1,4),w(1,16),w(1,7),gc_51,gc_58,amp(31))
2615 C Amplitude(s) for diagram number 32
2616  CALL ffv2_5_0(w(1,5),w(1,2),w(1,7),gc_51,gc_58,amp(32))
2617  CALL ffv1p0_3(w(1,1),w(1,3),gc_11,zero,zero,w(1,5))
2618  CALL ffv1_1(w(1,2),w(1,5),gc_11,zero,zero,w(1,16))
2619 C Amplitude(s) for diagram number 33
2620  CALL ffv1_0(w(1,4),w(1,16),w(1,12),gc_2,amp(33))
2621  CALL ffv1_2(w(1,4),w(1,5),gc_11,zero,zero,w(1,9))
2622 C Amplitude(s) for diagram number 34
2623  CALL ffv1_0(w(1,9),w(1,2),w(1,12),gc_2,amp(34))
2624 C Amplitude(s) for diagram number 35
2625  CALL ffv2_5_0(w(1,4),w(1,16),w(1,7),gc_51,gc_58,amp(35))
2626 C Amplitude(s) for diagram number 36
2627  CALL ffv2_5_0(w(1,9),w(1,2),w(1,7),gc_51,gc_58,amp(36))
2628  CALL ffv2_5_1(w(1,2),w(1,13),gc_51,gc_58,zero,zero,w(1,9))
2629 C Amplitude(s) for diagram number 37
2630  CALL ffv1_0(w(1,4),w(1,9),w(1,12),gc_2,amp(37))
2631  CALL ffv2_5_2(w(1,4),w(1,13),gc_51,gc_58,zero,zero,w(1,16))
2632 C Amplitude(s) for diagram number 38
2633  CALL ffv1_0(w(1,16),w(1,2),w(1,12),gc_2,amp(38))
2634 C Amplitude(s) for diagram number 39
2635  CALL ffv2_5_0(w(1,4),w(1,9),w(1,7),gc_51,gc_58,amp(39))
2636 C Amplitude(s) for diagram number 40
2637  CALL ffv2_5_0(w(1,16),w(1,2),w(1,7),gc_51,gc_58,amp(40))
2638  CALL ffv1_2(w(1,1),w(1,14),gc_2,zero,zero,w(1,16))
2639 C Amplitude(s) for diagram number 41
2640  CALL ffv1_0(w(1,16),w(1,3),w(1,12),gc_2,amp(41))
2641  CALL ffv1_2(w(1,1),w(1,12),gc_2,zero,zero,w(1,9))
2642 C Amplitude(s) for diagram number 42
2643  CALL ffv1_0(w(1,9),w(1,3),w(1,14),gc_2,amp(42))
2644 C Amplitude(s) for diagram number 43
2645  CALL ffv2_5_0(w(1,16),w(1,3),w(1,7),gc_51,gc_58,amp(43))
2646  CALL ffv2_5_2(w(1,1),w(1,7),gc_51,gc_58,zero,zero,w(1,16))
2647 C Amplitude(s) for diagram number 44
2648  CALL ffv1_0(w(1,16),w(1,3),w(1,14),gc_2,amp(44))
2649  CALL ffv1p0_3(w(1,4),w(1,2),gc_11,zero,zero,w(1,14))
2650  CALL ffv1_2(w(1,1),w(1,14),gc_11,zero,zero,w(1,13))
2651 C Amplitude(s) for diagram number 45
2652  CALL ffv1_0(w(1,13),w(1,3),w(1,12),gc_2,amp(45))
2653 C Amplitude(s) for diagram number 46
2654  CALL ffv1_0(w(1,9),w(1,3),w(1,14),gc_11,amp(46))
2655 C Amplitude(s) for diagram number 47
2656  CALL ffv2_5_0(w(1,13),w(1,3),w(1,7),gc_51,gc_58,amp(47))
2657 C Amplitude(s) for diagram number 48
2658  CALL ffv1_0(w(1,16),w(1,3),w(1,14),gc_11,amp(48))
2659  CALL ffv2_5_2(w(1,1),w(1,15),gc_51,gc_58,zero,zero,w(1,14))
2660 C Amplitude(s) for diagram number 49
2661  CALL ffv1_0(w(1,14),w(1,3),w(1,12),gc_2,amp(49))
2662 C Amplitude(s) for diagram number 50
2663  CALL ffv2_5_0(w(1,9),w(1,3),w(1,15),gc_51,gc_58,amp(50))
2664 C Amplitude(s) for diagram number 51
2665  CALL ffv2_5_0(w(1,14),w(1,3),w(1,7),gc_51,gc_58,amp(51))
2666 C Amplitude(s) for diagram number 52
2667  CALL ffv2_5_0(w(1,16),w(1,3),w(1,15),gc_51,gc_58,amp(52))
2668  CALL ffv1_2(w(1,1),w(1,8),gc_2,zero,zero,w(1,15))
2669 C Amplitude(s) for diagram number 53
2670  CALL ffv1_0(w(1,15),w(1,2),w(1,12),gc_2,amp(53))
2671 C Amplitude(s) for diagram number 54
2672  CALL ffv1_0(w(1,9),w(1,2),w(1,8),gc_2,amp(54))
2673 C Amplitude(s) for diagram number 55
2674  CALL ffv2_5_0(w(1,15),w(1,2),w(1,7),gc_51,gc_58,amp(55))
2675 C Amplitude(s) for diagram number 56
2676  CALL ffv1_0(w(1,16),w(1,2),w(1,8),gc_2,amp(56))
2677  CALL ffv1p0_3(w(1,4),w(1,3),gc_11,zero,zero,w(1,8))
2678  CALL ffv1_2(w(1,1),w(1,8),gc_11,zero,zero,w(1,4))
2679 C Amplitude(s) for diagram number 57
2680  CALL ffv1_0(w(1,4),w(1,2),w(1,12),gc_2,amp(57))
2681 C Amplitude(s) for diagram number 58
2682  CALL ffv1_0(w(1,9),w(1,2),w(1,8),gc_11,amp(58))
2683 C Amplitude(s) for diagram number 59
2684  CALL ffv2_5_0(w(1,4),w(1,2),w(1,7),gc_51,gc_58,amp(59))
2685 C Amplitude(s) for diagram number 60
2686  CALL ffv1_0(w(1,16),w(1,2),w(1,8),gc_11,amp(60))
2687  CALL ffv2_5_2(w(1,1),w(1,11),gc_51,gc_58,zero,zero,w(1,8))
2688 C Amplitude(s) for diagram number 61
2689  CALL ffv1_0(w(1,8),w(1,2),w(1,12),gc_2,amp(61))
2690 C Amplitude(s) for diagram number 62
2691  CALL ffv2_5_0(w(1,9),w(1,2),w(1,11),gc_51,gc_58,amp(62))
2692 C Amplitude(s) for diagram number 63
2693  CALL ffv2_5_0(w(1,8),w(1,2),w(1,7),gc_51,gc_58,amp(63))
2694 C Amplitude(s) for diagram number 64
2695  CALL ffv2_5_0(w(1,16),w(1,2),w(1,11),gc_51,gc_58,amp(64))
2696  jamp(1)=-amp(1)-amp(2)-amp(3)-amp(4)-amp(5)-amp(6)-amp(7)-amp(8)
2697  $ -amp(9)-amp(10)-amp(11)-amp(12)+1./6.*amp(13)+1./6.*amp(14)
2698  $ +1./6.*amp(15)+1./6.*amp(16)-amp(17)-amp(18)-amp(19)-amp(20)
2699  $ +1./2.*amp(33)+1./2.*amp(34)+1./2.*amp(35)+1./2.*amp(36)
2700  $ +1./2.*amp(45)+1./2.*amp(46)+1./2.*amp(47)+1./2.*amp(48)
2701  $ -amp(53)-amp(54)-amp(55)-amp(56)+1./6.*amp(57)+1./6.*amp(58)
2702  $ +1./6.*amp(59)+1./6.*amp(60)-amp(61)-amp(62)-amp(63)-amp(64)
2703  jamp(2)=-1./2.*amp(13)-1./2.*amp(14)-1./2.*amp(15)-1./2.*amp(16)
2704  $ +amp(21)+amp(22)+amp(23)+amp(24)+amp(25)+amp(26)+amp(27)
2705  $ +amp(28)+amp(29)+amp(30)+amp(31)+amp(32)-1./6.*amp(33)
2706  $ -1./6.*amp(34)-1./6.*amp(35)-1./6.*amp(36)+amp(37)+amp(38)
2707  $ +amp(39)+amp(40)+amp(41)+amp(42)+amp(43)+amp(44)-1./6.*amp(45)
2708  $ -1./6.*amp(46)-1./6.*amp(47)-1./6.*amp(48)+amp(49)+amp(50)
2709  $ +amp(51)+amp(52)-1./2.*amp(57)-1./2.*amp(58)-1./2.*amp(59)
2710  $ -1./2.*amp(60)
2711 
2712  matrix = 0.d0
2713  DO i = 1, ncolor
2714  ztemp = (0.d0,0.d0)
2715  DO j = 1, ncolor
2716  ztemp = ztemp + cf(j,i)*jamp(j)
2717  ENDDO
2718  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
2719  ENDDO
2720  matrix_ccx_ccx_noh=matrix
2721  ENDIF
2722  ENDIF
2723  END
2724 
2725 C -----------------SUBPROCESS CCX->DSX, NO HIGGS
2726 
2727  SUBROUTINE ccx_dsx_noh(P,H1,H2,ANS)
2728 C
2729 C
2730 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
2731 C By the MadGraph Development Team
2732 C Please visit us at https://launchpad.net/madgraph5
2733 C
2734 C MadGraph StandAlone Version
2735 C
2736 C Returns amplitude squared summed/avg over colors
2737 C and helicities
2738 C for the point in phase space P(0:3,NEXTERNAL)
2739 C
2740 C Process: c c~ > d s~ ta+ ta- / h Qed=4
2741 C
2742  IMPLICIT NONE
2743 C
2744 C CONSTANTS
2745 C
2746  INTEGER nexternal
2747  parameter(nexternal=6)
2748  INTEGER ncomb
2749  parameter( ncomb=64)
2750 C
2751 C ARGUMENTS
2752 C
2753  REAL*8 p(0:3,nexternal),ans
2754  INTEGER h1,h2
2755 C
2756 C LOCAL VARIABLES
2757 C
2758  INTEGER nhel(nexternal,ncomb),ntry
2759  REAL*8 t
2760  REAL*8 matrix_ccx_dsx_noh
2761  INTEGER ihel,iden, i
2762  INTEGER jc(nexternal)
2763  LOGICAL goodhel(ncomb)
2764  DATA ntry/0/
2765  DATA goodhel/ncomb*.false./
2766  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
2767  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
2768  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
2769  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
2770  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
2771  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
2772  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
2773  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
2774  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
2775  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
2776  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
2777  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
2778  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
2779  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
2780  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
2781  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
2782  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
2783  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
2784  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
2785  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
2786  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
2787  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
2788  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
2789  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
2790  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
2791  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
2792  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
2793  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
2794  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
2795  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
2796  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
2797  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
2798  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
2799  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
2800  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
2801  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
2802  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
2803  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
2804  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
2805  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
2806  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
2807  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
2808  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
2809  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
2810  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
2811  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
2812  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
2813  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
2814  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
2815  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
2816  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
2817  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
2818  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
2819  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
2820  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
2821  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
2822  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
2823  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
2824  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
2825  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
2826  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
2827  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
2828  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
2829  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
2830  DATA iden/36/
2831 C ----------
2832 C BEGIN CODE
2833 C ----------
2834  DO ihel=1,nexternal
2835  jc(ihel) = +1
2836  ENDDO
2837  ans = 0d0
2838  DO ihel=1,ncomb
2839  t=matrix_ccx_dsx_noh(p ,h1,h2,nhel(1,ihel),jc(1))
2840  ans=ans+t
2841  ENDDO
2842  ans=ans/dble(iden)
2843  END
2844 
2845 
2846  REAL*8 FUNCTION matrix_ccx_dsx_noh(P,H1,H2,NHEL,IC)
2847 C
2848 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
2849 C By the MadGraph Development Team
2850 C Please visit us at https://launchpad.net/madgraph5
2851 C
2852 C Returns amplitude squared summed/avg over colors
2853 C for the point with external lines W(0:6,NEXTERNAL)
2854 C
2855 C Process: c c~ > d s~ ta+ ta- / h Qed=4
2856 C
2857  IMPLICIT NONE
2858 C
2859 C CONSTANTS
2860 C
2861  INTEGER ngraphs
2862  parameter(ngraphs=11)
2863  INTEGER nexternal
2864  parameter(nexternal=6)
2865  INTEGER nwavefuncs, ncolor
2866  parameter(nwavefuncs=10, ncolor=1)
2867  REAL*8 zero
2868  parameter(zero=0d0)
2869  COMPLEX*16 imag1
2870  parameter(imag1=(0d0,1d0))
2871 C
2872 C ARGUMENTS
2873 C
2874  REAL*8 p(0:3,nexternal)
2875  INTEGER nhel(nexternal), ic(nexternal)
2876 C
2877 C LOCAL VARIABLES
2878 C
2879  INTEGER i,j
2880  COMPLEX*16 ztemp
2881  REAL*8 denom(ncolor), cf(ncolor,ncolor)
2882  COMPLEX*16 amp(ngraphs), jamp(ncolor)
2883  COMPLEX*16 w(18,nwavefuncs)
2884  COMPLEX*16 dum0,dum1
2885  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
2886 C
2887 C GLOBAL VARIABLES
2888 C
2889  include 'coupl.inc'
2890 C
2891 C COLOR DATA
2892 C
2893  DATA denom(1)/1/
2894  DATA (cf(i, 1),i= 1, 1) / 9/
2895 C 1 T(2,4) T(3,1)
2896 
2897  INTEGER h1,h2
2898  REAL*8 matrix
2899  matrix_ccx_dsx_noh=0d0
2900  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
2901  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
2902 
2903 C ----------
2904 C BEGIN CODE
2905 C ----------
2906  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
2907  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
2908  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
2909  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
2910  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
2911  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
2912  CALL ffv2_3(w(1,1),w(1,3),gc_44,mw,ww,w(1,7))
2913  CALL ffv2_3(w(1,4),w(1,2),gc_100,mw,ww,w(1,8))
2914  CALL ffv2_2(w(1,5),w(1,7),gc_108,zero,zero,w(1,9))
2915 C Amplitude(s) for diagram number 1
2916  CALL ffv2_0(w(1,9),w(1,6),w(1,8),gc_108,amp(1))
2917  CALL ffv1p0_3(w(1,5),w(1,6),gc_3,zero,zero,w(1,9))
2918 C Amplitude(s) for diagram number 2
2919  CALL vvv1_0(w(1,9),w(1,7),w(1,8),gc_4,amp(2))
2920  CALL ffv2_4_3(w(1,5),w(1,6),gc_50,gc_59,mz,wz,w(1,10))
2921 C Amplitude(s) for diagram number 3
2922  CALL vvv1_0(w(1,7),w(1,8),w(1,10),gc_53,amp(3))
2923  CALL ffv2_1(w(1,2),w(1,7),gc_100,zero,zero,w(1,6))
2924 C Amplitude(s) for diagram number 4
2925  CALL ffv1_0(w(1,4),w(1,6),w(1,9),gc_1,amp(4))
2926  CALL ffv2_2(w(1,4),w(1,7),gc_100,zero,zero,w(1,5))
2927 C Amplitude(s) for diagram number 5
2928  CALL ffv1_0(w(1,5),w(1,2),w(1,9),gc_2,amp(5))
2929 C Amplitude(s) for diagram number 6
2930  CALL ffv2_3_0(w(1,4),w(1,6),w(1,10),gc_50,gc_58,amp(6))
2931 C Amplitude(s) for diagram number 7
2932  CALL ffv2_5_0(w(1,5),w(1,2),w(1,10),gc_51,gc_58,amp(7))
2933  CALL ffv2_2(w(1,1),w(1,8),gc_44,zero,zero,w(1,5))
2934 C Amplitude(s) for diagram number 8
2935  CALL ffv1_0(w(1,5),w(1,3),w(1,9),gc_1,amp(8))
2936  CALL ffv1_2(w(1,1),w(1,9),gc_2,zero,zero,w(1,2))
2937 C Amplitude(s) for diagram number 9
2938  CALL ffv2_0(w(1,2),w(1,3),w(1,8),gc_44,amp(9))
2939 C Amplitude(s) for diagram number 10
2940  CALL ffv2_3_0(w(1,5),w(1,3),w(1,10),gc_50,gc_58,amp(10))
2941  CALL ffv2_5_2(w(1,1),w(1,10),gc_51,gc_58,zero,zero,w(1,5))
2942 C Amplitude(s) for diagram number 11
2943  CALL ffv2_0(w(1,5),w(1,3),w(1,8),gc_44,amp(11))
2944  jamp(1)=+amp(1)+amp(2)+amp(3)+amp(4)+amp(5)+amp(6)+amp(7)+amp(8)
2945  $ +amp(9)+amp(10)+amp(11)
2946 
2947  matrix = 0.d0
2948  DO i = 1, ncolor
2949  ztemp = (0.d0,0.d0)
2950  DO j = 1, ncolor
2951  ztemp = ztemp + cf(j,i)*jamp(j)
2952  ENDDO
2953  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
2954  ENDDO
2955  matrix_ccx_dsx_noh=matrix
2956  ENDIF
2957  ENDIF
2958  END
2959 
2960 C ----------------SUBPROCESS CCX->SDX, NO HIGGS
2961 
2962  SUBROUTINE ccx_sdx_noh(P,H1,H2,ANS)
2963 C
2964 C
2965 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
2966 C By the MadGraph Development Team
2967 C Please visit us at https://launchpad.net/madgraph5
2968 C
2969 C MadGraph StandAlone Version
2970 C
2971 C Returns amplitude squared summed/avg over colors
2972 C and helicities
2973 C for the point in phase space P(0:3,NEXTERNAL)
2974 C
2975 C Process: c c~ > s d~ ta+ ta- / h Qed=4
2976 C
2977  IMPLICIT NONE
2978 C
2979 C CONSTANTS
2980 C
2981  INTEGER nexternal
2982  parameter(nexternal=6)
2983  INTEGER ncomb
2984  parameter( ncomb=64)
2985 C
2986 C ARGUMENTS
2987 C
2988  REAL*8 p(0:3,nexternal),ans
2989  INTEGER h1,h2
2990 C
2991 C LOCAL VARIABLES
2992 C
2993  INTEGER nhel(nexternal,ncomb),ntry
2994  REAL*8 t
2995  REAL*8 matrix_ccx_sdx_noh
2996  INTEGER ihel,iden, i
2997  INTEGER jc(nexternal)
2998  LOGICAL goodhel(ncomb)
2999  DATA ntry/0/
3000  DATA goodhel/ncomb*.false./
3001  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
3002  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
3003  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
3004  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
3005  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
3006  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
3007  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
3008  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
3009  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
3010  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
3011  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
3012  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
3013  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
3014  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
3015  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
3016  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
3017  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
3018  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
3019  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
3020  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
3021  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
3022  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
3023  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
3024  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
3025  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
3026  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
3027  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
3028  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
3029  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
3030  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
3031  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
3032  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
3033  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
3034  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
3035  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
3036  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
3037  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
3038  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
3039  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
3040  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
3041  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
3042  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
3043  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
3044  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
3045  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
3046  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
3047  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
3048  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
3049  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
3050  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
3051  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
3052  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
3053  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
3054  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
3055  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
3056  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
3057  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
3058  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
3059  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
3060  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
3061  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
3062  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
3063  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
3064  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
3065  DATA iden/36/
3066 C ----------
3067 C BEGIN CODE
3068 C ----------
3069  DO ihel=1,nexternal
3070  jc(ihel) = +1
3071  ENDDO
3072  ans = 0d0
3073  DO ihel=1,ncomb
3074  t=matrix_ccx_sdx_noh(p ,h1,h2,nhel(1,ihel),jc(1))
3075  ans=ans+t
3076  ENDDO
3077  ans=ans/dble(iden)
3078  END
3079 
3080 
3081  REAL*8 FUNCTION matrix_ccx_sdx_noh(P,H1,H2,NHEL,IC)
3082 C
3083 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
3084 C By the MadGraph Development Team
3085 C Please visit us at https://launchpad.net/madgraph5
3086 C
3087 C Returns amplitude squared summed/avg over colors
3088 C for the point with external lines W(0:6,NEXTERNAL)
3089 C
3090 C Process: c c~ > s d~ ta+ ta- / h Qed=4
3091 C
3092  IMPLICIT NONE
3093 C
3094 C CONSTANTS
3095 C
3096  INTEGER ngraphs
3097  parameter(ngraphs=11)
3098  INTEGER nexternal
3099  parameter(nexternal=6)
3100  INTEGER nwavefuncs, ncolor
3101  parameter(nwavefuncs=10, ncolor=1)
3102  REAL*8 zero
3103  parameter(zero=0d0)
3104  COMPLEX*16 imag1
3105  parameter(imag1=(0d0,1d0))
3106 C
3107 C ARGUMENTS
3108 C
3109  REAL*8 p(0:3,nexternal)
3110  INTEGER nhel(nexternal), ic(nexternal)
3111 C
3112 C LOCAL VARIABLES
3113 C
3114  INTEGER i,j
3115  COMPLEX*16 ztemp
3116  REAL*8 denom(ncolor), cf(ncolor,ncolor)
3117  COMPLEX*16 amp(ngraphs), jamp(ncolor)
3118  COMPLEX*16 w(18,nwavefuncs)
3119  COMPLEX*16 dum0,dum1
3120  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
3121 C
3122 C GLOBAL VARIABLES
3123 C
3124  include 'coupl.inc'
3125 C
3126 C COLOR DATA
3127 C
3128  DATA denom(1)/1/
3129  DATA (cf(i, 1),i= 1, 1) / 9/
3130 C 1 T(2,4) T(3,1)
3131 
3132  INTEGER h1,h2
3133  REAL*8 matrix
3134  matrix_ccx_sdx_noh=0d0
3135  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
3136  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
3137 
3138 C ----------
3139 C BEGIN CODE
3140 C ----------
3141  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
3142  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
3143  CALL oxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
3144  CALL ixxxxx(p(0,4),zero,nhel(4),-1*ic(4),w(1,4))
3145  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
3146  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
3147  CALL ffv2_3(w(1,1),w(1,3),gc_100,mw,ww,w(1,7))
3148  CALL ffv2_3(w(1,4),w(1,2),gc_44,mw,ww,w(1,8))
3149  CALL ffv2_2(w(1,5),w(1,7),gc_108,zero,zero,w(1,9))
3150 C Amplitude(s) for diagram number 1
3151  CALL ffv2_0(w(1,9),w(1,6),w(1,8),gc_108,amp(1))
3152  CALL ffv1p0_3(w(1,5),w(1,6),gc_3,zero,zero,w(1,9))
3153 C Amplitude(s) for diagram number 2
3154  CALL vvv1_0(w(1,9),w(1,7),w(1,8),gc_4,amp(2))
3155  CALL ffv2_4_3(w(1,5),w(1,6),gc_50,gc_59,mz,wz,w(1,10))
3156 C Amplitude(s) for diagram number 3
3157  CALL vvv1_0(w(1,7),w(1,8),w(1,10),gc_53,amp(3))
3158  CALL ffv2_1(w(1,2),w(1,7),gc_44,zero,zero,w(1,6))
3159 C Amplitude(s) for diagram number 4
3160  CALL ffv1_0(w(1,4),w(1,6),w(1,9),gc_1,amp(4))
3161  CALL ffv2_2(w(1,4),w(1,7),gc_44,zero,zero,w(1,5))
3162 C Amplitude(s) for diagram number 5
3163  CALL ffv1_0(w(1,5),w(1,2),w(1,9),gc_2,amp(5))
3164 C Amplitude(s) for diagram number 6
3165  CALL ffv2_3_0(w(1,4),w(1,6),w(1,10),gc_50,gc_58,amp(6))
3166 C Amplitude(s) for diagram number 7
3167  CALL ffv2_5_0(w(1,5),w(1,2),w(1,10),gc_51,gc_58,amp(7))
3168  CALL ffv2_2(w(1,1),w(1,8),gc_100,zero,zero,w(1,5))
3169 C Amplitude(s) for diagram number 8
3170  CALL ffv1_0(w(1,5),w(1,3),w(1,9),gc_1,amp(8))
3171  CALL ffv1_2(w(1,1),w(1,9),gc_2,zero,zero,w(1,2))
3172 C Amplitude(s) for diagram number 9
3173  CALL ffv2_0(w(1,2),w(1,3),w(1,8),gc_100,amp(9))
3174 C Amplitude(s) for diagram number 10
3175  CALL ffv2_3_0(w(1,5),w(1,3),w(1,10),gc_50,gc_58,amp(10))
3176  CALL ffv2_5_2(w(1,1),w(1,10),gc_51,gc_58,zero,zero,w(1,5))
3177 C Amplitude(s) for diagram number 11
3178  CALL ffv2_0(w(1,5),w(1,3),w(1,8),gc_100,amp(11))
3179  jamp(1)=+amp(1)+amp(2)+amp(3)+amp(4)+amp(5)+amp(6)+amp(7)+amp(8)
3180  $ +amp(9)+amp(10)+amp(11)
3181 
3182  matrix = 0.d0
3183  DO i = 1, ncolor
3184  ztemp = (0.d0,0.d0)
3185  DO j = 1, ncolor
3186  ztemp = ztemp + cf(j,i)*jamp(j)
3187  ENDDO
3188  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
3189  ENDDO
3190  matrix_ccx_sdx_noh=matrix
3191  ENDIF
3192  ENDIF
3193  END
3194 
3195 CCCCCCCCCCCCCCCCCC
3196 
3197 C --- BEGIN SUBROUTINE CCX->GG NO HIGGS
3198 
3199 
3200  SUBROUTINE ccx_gg_noh(P,H1,H2,ANS)
3201 C
3202 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
3203 C By the MadGraph Development Team
3204 C Please visit us at https://launchpad.net/madgraph5
3205 C
3206 C MadGraph StandAlone Version
3207 C
3208 C Returns amplitude squared summed/avg over colors
3209 C and helicities
3210 C for the point in phase space P(0:3,NEXTERNAL)
3211 C
3212 C Process: c c~ > g g ta+ ta- / h Qed=4
3213 C
3214  IMPLICIT NONE
3215 C
3216 C CONSTANTS
3217 C
3218  INTEGER nexternal
3219  parameter(nexternal=6)
3220  INTEGER ncomb
3221  parameter( ncomb=64)
3222 C
3223 C ARGUMENTS
3224 C
3225  REAL*8 p(0:3,nexternal),ans
3226  INTEGER h1,h2
3227 C
3228 C LOCAL VARIABLES
3229 C
3230  INTEGER nhel(nexternal,ncomb),ntry
3231  REAL*8 t
3232  REAL*8 matrix_ccx_gg_noh
3233  INTEGER ihel,iden, i
3234  INTEGER jc(nexternal)
3235  LOGICAL goodhel(ncomb)
3236  DATA ntry/0/
3237  DATA goodhel/ncomb*.false./
3238  DATA (nhel(i, 1),i=1,6) /-1,-1,-1,-1,-1,-1/
3239  DATA (nhel(i, 2),i=1,6) /-1,-1,-1,-1,-1, 1/
3240  DATA (nhel(i, 3),i=1,6) /-1,-1,-1,-1, 1,-1/
3241  DATA (nhel(i, 4),i=1,6) /-1,-1,-1,-1, 1, 1/
3242  DATA (nhel(i, 5),i=1,6) /-1,-1,-1, 1,-1,-1/
3243  DATA (nhel(i, 6),i=1,6) /-1,-1,-1, 1,-1, 1/
3244  DATA (nhel(i, 7),i=1,6) /-1,-1,-1, 1, 1,-1/
3245  DATA (nhel(i, 8),i=1,6) /-1,-1,-1, 1, 1, 1/
3246  DATA (nhel(i, 9),i=1,6) /-1,-1, 1,-1,-1,-1/
3247  DATA (nhel(i, 10),i=1,6) /-1,-1, 1,-1,-1, 1/
3248  DATA (nhel(i, 11),i=1,6) /-1,-1, 1,-1, 1,-1/
3249  DATA (nhel(i, 12),i=1,6) /-1,-1, 1,-1, 1, 1/
3250  DATA (nhel(i, 13),i=1,6) /-1,-1, 1, 1,-1,-1/
3251  DATA (nhel(i, 14),i=1,6) /-1,-1, 1, 1,-1, 1/
3252  DATA (nhel(i, 15),i=1,6) /-1,-1, 1, 1, 1,-1/
3253  DATA (nhel(i, 16),i=1,6) /-1,-1, 1, 1, 1, 1/
3254  DATA (nhel(i, 17),i=1,6) /-1, 1,-1,-1,-1,-1/
3255  DATA (nhel(i, 18),i=1,6) /-1, 1,-1,-1,-1, 1/
3256  DATA (nhel(i, 19),i=1,6) /-1, 1,-1,-1, 1,-1/
3257  DATA (nhel(i, 20),i=1,6) /-1, 1,-1,-1, 1, 1/
3258  DATA (nhel(i, 21),i=1,6) /-1, 1,-1, 1,-1,-1/
3259  DATA (nhel(i, 22),i=1,6) /-1, 1,-1, 1,-1, 1/
3260  DATA (nhel(i, 23),i=1,6) /-1, 1,-1, 1, 1,-1/
3261  DATA (nhel(i, 24),i=1,6) /-1, 1,-1, 1, 1, 1/
3262  DATA (nhel(i, 25),i=1,6) /-1, 1, 1,-1,-1,-1/
3263  DATA (nhel(i, 26),i=1,6) /-1, 1, 1,-1,-1, 1/
3264  DATA (nhel(i, 27),i=1,6) /-1, 1, 1,-1, 1,-1/
3265  DATA (nhel(i, 28),i=1,6) /-1, 1, 1,-1, 1, 1/
3266  DATA (nhel(i, 29),i=1,6) /-1, 1, 1, 1,-1,-1/
3267  DATA (nhel(i, 30),i=1,6) /-1, 1, 1, 1,-1, 1/
3268  DATA (nhel(i, 31),i=1,6) /-1, 1, 1, 1, 1,-1/
3269  DATA (nhel(i, 32),i=1,6) /-1, 1, 1, 1, 1, 1/
3270  DATA (nhel(i, 33),i=1,6) / 1,-1,-1,-1,-1,-1/
3271  DATA (nhel(i, 34),i=1,6) / 1,-1,-1,-1,-1, 1/
3272  DATA (nhel(i, 35),i=1,6) / 1,-1,-1,-1, 1,-1/
3273  DATA (nhel(i, 36),i=1,6) / 1,-1,-1,-1, 1, 1/
3274  DATA (nhel(i, 37),i=1,6) / 1,-1,-1, 1,-1,-1/
3275  DATA (nhel(i, 38),i=1,6) / 1,-1,-1, 1,-1, 1/
3276  DATA (nhel(i, 39),i=1,6) / 1,-1,-1, 1, 1,-1/
3277  DATA (nhel(i, 40),i=1,6) / 1,-1,-1, 1, 1, 1/
3278  DATA (nhel(i, 41),i=1,6) / 1,-1, 1,-1,-1,-1/
3279  DATA (nhel(i, 42),i=1,6) / 1,-1, 1,-1,-1, 1/
3280  DATA (nhel(i, 43),i=1,6) / 1,-1, 1,-1, 1,-1/
3281  DATA (nhel(i, 44),i=1,6) / 1,-1, 1,-1, 1, 1/
3282  DATA (nhel(i, 45),i=1,6) / 1,-1, 1, 1,-1,-1/
3283  DATA (nhel(i, 46),i=1,6) / 1,-1, 1, 1,-1, 1/
3284  DATA (nhel(i, 47),i=1,6) / 1,-1, 1, 1, 1,-1/
3285  DATA (nhel(i, 48),i=1,6) / 1,-1, 1, 1, 1, 1/
3286  DATA (nhel(i, 49),i=1,6) / 1, 1,-1,-1,-1,-1/
3287  DATA (nhel(i, 50),i=1,6) / 1, 1,-1,-1,-1, 1/
3288  DATA (nhel(i, 51),i=1,6) / 1, 1,-1,-1, 1,-1/
3289  DATA (nhel(i, 52),i=1,6) / 1, 1,-1,-1, 1, 1/
3290  DATA (nhel(i, 53),i=1,6) / 1, 1,-1, 1,-1,-1/
3291  DATA (nhel(i, 54),i=1,6) / 1, 1,-1, 1,-1, 1/
3292  DATA (nhel(i, 55),i=1,6) / 1, 1,-1, 1, 1,-1/
3293  DATA (nhel(i, 56),i=1,6) / 1, 1,-1, 1, 1, 1/
3294  DATA (nhel(i, 57),i=1,6) / 1, 1, 1,-1,-1,-1/
3295  DATA (nhel(i, 58),i=1,6) / 1, 1, 1,-1,-1, 1/
3296  DATA (nhel(i, 59),i=1,6) / 1, 1, 1,-1, 1,-1/
3297  DATA (nhel(i, 60),i=1,6) / 1, 1, 1,-1, 1, 1/
3298  DATA (nhel(i, 61),i=1,6) / 1, 1, 1, 1,-1,-1/
3299  DATA (nhel(i, 62),i=1,6) / 1, 1, 1, 1,-1, 1/
3300  DATA (nhel(i, 63),i=1,6) / 1, 1, 1, 1, 1,-1/
3301  DATA (nhel(i, 64),i=1,6) / 1, 1, 1, 1, 1, 1/
3302  DATA iden/72/
3303 C ----------
3304 C BEGIN CODE
3305 C ----------
3306  DO ihel=1,nexternal
3307  jc(ihel) = +1
3308  ENDDO
3309  ans = 0d0
3310  DO ihel=1,ncomb
3311  t=matrix_ccx_gg_noh(p ,h1,h2,nhel(1,ihel),jc(1))
3312  ans=ans+t
3313  ENDDO
3314  ans=ans/dble(iden)
3315  END
3316 
3317 
3318  REAL*8 FUNCTION matrix_ccx_gg_noh(P,H1,H2,NHEL,IC)
3319 C
3320 C Generated by MadGraph 5 v. 1.5.15, 2013-12-11
3321 C By the MadGraph Development Team
3322 C Please visit us at https://launchpad.net/madgraph5
3323 C
3324 C Returns amplitude squared summed/avg over colors
3325 C for the point with external lines W(0:6,NEXTERNAL)
3326 C
3327 C Process: c c~ > g g ta+ ta- / h Qed=4
3328 C
3329  IMPLICIT NONE
3330 C
3331 C CONSTANTS
3332 C
3333  INTEGER ngraphs
3334  parameter(ngraphs=16)
3335  INTEGER nexternal
3336  parameter(nexternal=6)
3337  INTEGER nwavefuncs, ncolor
3338  parameter(nwavefuncs=10, ncolor=2)
3339  REAL*8 zero
3340  parameter(zero=0d0)
3341  COMPLEX*16 imag1
3342  parameter(imag1=(0d0,1d0))
3343 C
3344 C ARGUMENTS
3345 C
3346  REAL*8 p(0:3,nexternal)
3347  INTEGER nhel(nexternal), ic(nexternal)
3348 C
3349 C LOCAL VARIABLES
3350 C
3351  INTEGER i,j
3352  COMPLEX*16 ztemp
3353  REAL*8 denom(ncolor), cf(ncolor,ncolor)
3354  COMPLEX*16 amp(ngraphs), jamp(ncolor)
3355  COMPLEX*16 w(18,nwavefuncs)
3356  COMPLEX*16 dum0,dum1
3357  DATA dum0, dum1/(0d0, 0d0), (1d0, 0d0)/
3358 C
3359 C GLOBAL VARIABLES
3360 C
3361  include 'coupl.inc'
3362 C
3363 C COLOR DATA
3364 C
3365  DATA denom(1)/3/
3366  DATA (cf(i, 1),i= 1, 2) / 16, -2/
3367 C 1 T(3,4,2,1)
3368  DATA denom(2)/3/
3369  DATA (cf(i, 2),i= 1, 2) / -2, 16/
3370 C 1 T(4,3,2,1)
3371 
3372  INTEGER h1,h2
3373  REAL*8 matrix
3374  matrix_ccx_gg_noh=0d0
3375  IF(h1.EQ.0. or .h1.EQ.nhel(5)) THEN
3376  IF(h2.EQ.0. or .h2.EQ.nhel(6)) THEN
3377 
3378 C ----------
3379 C BEGIN CODE
3380 C ----------
3381  CALL ixxxxx(p(0,1),zero,nhel(1),+1*ic(1),w(1,1))
3382  CALL oxxxxx(p(0,2),zero,nhel(2),-1*ic(2),w(1,2))
3383  CALL vxxxxx(p(0,3),zero,nhel(3),+1*ic(3),w(1,3))
3384  CALL vxxxxx(p(0,4),zero,nhel(4),+1*ic(4),w(1,4))
3385  CALL ixxxxx(p(0,5),mta,nhel(5),-1*ic(5),w(1,5))
3386  CALL oxxxxx(p(0,6),mta,nhel(6),+1*ic(6),w(1,6))
3387  CALL ffv1_2(w(1,1),w(1,3),gc_11,zero,zero,w(1,7))
3388  CALL ffv1_1(w(1,2),w(1,4),gc_11,zero,zero,w(1,8))
3389  CALL ffv1p0_3(w(1,5),w(1,6),gc_3,zero,zero,w(1,9))
3390 C Amplitude(s) for diagram number 1
3391  CALL ffv1_0(w(1,7),w(1,8),w(1,9),gc_2,amp(1))
3392  CALL ffv2_4_3(w(1,5),w(1,6),gc_50,gc_59,mz,wz,w(1,10))
3393 C Amplitude(s) for diagram number 2
3394  CALL ffv2_5_0(w(1,7),w(1,8),w(1,10),gc_51,gc_58,amp(2))
3395  CALL ffv1_2(w(1,7),w(1,4),gc_11,zero,zero,w(1,6))
3396 C Amplitude(s) for diagram number 3
3397  CALL ffv1_0(w(1,6),w(1,2),w(1,9),gc_2,amp(3))
3398 C Amplitude(s) for diagram number 4
3399  CALL ffv2_5_0(w(1,6),w(1,2),w(1,10),gc_51,gc_58,amp(4))
3400  CALL ffv1_2(w(1,1),w(1,4),gc_11,zero,zero,w(1,6))
3401  CALL ffv1_1(w(1,2),w(1,3),gc_11,zero,zero,w(1,7))
3402 C Amplitude(s) for diagram number 5
3403  CALL ffv1_0(w(1,6),w(1,7),w(1,9),gc_2,amp(5))
3404 C Amplitude(s) for diagram number 6
3405  CALL ffv2_5_0(w(1,6),w(1,7),w(1,10),gc_51,gc_58,amp(6))
3406  CALL ffv1_2(w(1,6),w(1,3),gc_11,zero,zero,w(1,5))
3407 C Amplitude(s) for diagram number 7
3408  CALL ffv1_0(w(1,5),w(1,2),w(1,9),gc_2,amp(7))
3409 C Amplitude(s) for diagram number 8
3410  CALL ffv2_5_0(w(1,5),w(1,2),w(1,10),gc_51,gc_58,amp(8))
3411  CALL ffv1_2(w(1,1),w(1,9),gc_2,zero,zero,w(1,5))
3412 C Amplitude(s) for diagram number 9
3413  CALL ffv1_0(w(1,5),w(1,7),w(1,4),gc_11,amp(9))
3414  CALL ffv2_5_2(w(1,1),w(1,10),gc_51,gc_58,zero,zero,w(1,6))
3415 C Amplitude(s) for diagram number 10
3416  CALL ffv1_0(w(1,6),w(1,7),w(1,4),gc_11,amp(10))
3417 C Amplitude(s) for diagram number 11
3418  CALL ffv1_0(w(1,5),w(1,8),w(1,3),gc_11,amp(11))
3419 C Amplitude(s) for diagram number 12
3420  CALL ffv1_0(w(1,6),w(1,8),w(1,3),gc_11,amp(12))
3421  CALL vvv1p0_1(w(1,3),w(1,4),gc_10,zero,zero,w(1,8))
3422  CALL ffv1_2(w(1,1),w(1,8),gc_11,zero,zero,w(1,4))
3423 C Amplitude(s) for diagram number 13
3424  CALL ffv1_0(w(1,4),w(1,2),w(1,9),gc_2,amp(13))
3425 C Amplitude(s) for diagram number 14
3426  CALL ffv1_0(w(1,5),w(1,2),w(1,8),gc_11,amp(14))
3427 C Amplitude(s) for diagram number 15
3428  CALL ffv2_5_0(w(1,4),w(1,2),w(1,10),gc_51,gc_58,amp(15))
3429 C Amplitude(s) for diagram number 16
3430  CALL ffv1_0(w(1,6),w(1,2),w(1,8),gc_11,amp(16))
3431  jamp(1)=+amp(5)+amp(6)+amp(7)+amp(8)+amp(9)+amp(10)-imag1
3432  $ *amp(13)-imag1*amp(14)-imag1*amp(15)-imag1*amp(16)
3433  jamp(2)=+amp(1)+amp(2)+amp(3)+amp(4)+amp(11)+amp(12)+imag1
3434  $ *amp(13)+imag1*amp(14)+imag1*amp(15)+imag1*amp(16)
3435 
3436  matrix = 0.d0
3437  DO i = 1, ncolor
3438  ztemp = (0.d0,0.d0)
3439  DO j = 1, ncolor
3440  ztemp = ztemp + cf(j,i)*jamp(j)
3441  ENDDO
3442  matrix = matrix+ztemp*dconjg(jamp(i))/denom(i)
3443  ENDDO
3444  matrix_ccx_gg_noh=matrix
3445  ENDIF
3446  ENDIF
3447  END
3448 
3449