]> git.uio.no Git - u/mrichter/AliRoot.git/blame - ISAJET/isasusy/sshhx.F
New version withe right table for monitorDeclareTable
[u/mrichter/AliRoot.git] / ISAJET / isasusy / sshhx.F
CommitLineData
0795afa3 1#include "isajet/pilot.h"
2 SUBROUTINE SSHHX
3C-----------------------------------------------------------------------
4C Calculates the decays Hi -> Hj + X.
5C
6C Includes vertex corrections for triple Higgs couplings due
7C to top and stop quarks effects.
8C See Kunszt and Zwirner CERN-TH.6150/91 for all but hh-hc-hc
9C correction which is in our Higgs-->SUSY paper:
10C Baer et. al. FSU-HEP-920630 or UH-511-749-92.
11C
12C The hh-hl-hl vertex correction now includes both
13C top & bottom and stop and sbottom squark
14C (non-degenerate with mixing) effects.
15C A-terms and mu=-2m1 are also included.
16C
17C
18C Bisset's HIGPRO
19C-----------------------------------------------------------------------
20#if defined(CERNLIB_IMPNONE)
21 IMPLICIT NONE
22#endif
23#include "isajet/sspar.inc"
24#include "isajet/sssm.inc"
25#include "isajet/sstype.inc"
26C
27 DOUBLE PRECISION PI,SR2,G2,GP2,BETA,ALPHA,SW2,CW2,LGTST,CBMA
28 $,SBMA,LAMB1,DWID,DELLPP,MH,M1,M2,LAMB,TEMP,DTEMPL,DTEMPR
29 $,DELHLL,DELHPP,DELHCC,CAB2,SAB2
30 DOUBLE PRECISION SSDLAM
31 REAL WID,ASMT,MTMT,MTQ,SUALFS,HIGFRZ
32 DOUBLE PRECISION SSMQCD
33C
34 PI=4.*ATAN(1.D0)
35 SR2=SQRT(2.D0)
36 G2=4.0*PI*ALFAEM/SN2THW
37 GP2=4*PI*ALFAEM/(1-SN2THW)
38 HIGFRZ=SQRT(AMTLSS*AMTRSS)
39 ASMT=SUALFS(AMTP**2,.36,AMTP,3)
40 MTMT=AMTP/(1.+4*ASMT/3./PI+(16.11-1.04*(5.-6.63/AMTP))*
41 $(ASMT/PI)**2)
42 MTQ=SSMQCD(DBLE(MTMT),DBLE(HIGFRZ))
43
44 BETA=ATAN(1.0/RV2V1)
45 ALPHA=ALFAH
46 SW2=SN2THW
47 CW2=1.-SN2THW
48C
49 LGTST=(1+(AMTLSS/MTQ)**2)*(1+(AMTRSS/MTQ)**2)
50 LGTST=LOG(LGTST)
51 SBMA=SIN(BETA-ALPHA)
52 CBMA=COS(BETA-ALPHA)
53 CAB2=(DCOS(ALPHA+BETA))**2
54 SAB2=1.0-CAB2
55C
56C hl0 -> ha0 + ha0
57C
58 IF(AMHL.GT.2*AMHA) THEN
59 LAMB1=AMHL**2-4.0*AMHA**2
60 DWID=SBMA*COS(2.0*BETA)
61C Now add hl-hp-hp vertex correction
62 DELLPP=3.0*G2*CW2*(MTQ**4)*COS(ALPHA)
63 DELLPP=DELLPP*(COS(BETA)**2)/(16.0*(PI**2))
64 DELLPP=DELLPP/((AMW**4)*(SIN(BETA))**3)
65 DELLPP=DELLPP*LGTST
66 DWID=(DWID+DELLPP)**2
67 DWID=DWID*G2*(AMZ**2)/(128.0*PI*CW2*(AMHL**2))
68 DWID=DWID*SQRT(LAMB1)
69 WID=DWID
70 CALL SSSAVE(ISHL,WID,ISHA,ISHA,0,0,0)
71 ENDIF
72C
73C hh -> ha + z
74C
75 IF(AMHH.GT.AMHA+AMZ) THEN
76 MH=AMHH
77 M1=AMHA
78 M2=AMZ
79 LAMB=SSDLAM(MH**2,M1**2,M2**2)
80 DWID=SQRT(G2*CW2)+SQRT(GP2*SW2)
81 DWID=DWID**2*SAB2*SQRT(LAMB)
82 DWID=DWID/(64.0*PI*(AMZ**2)*(AMHH**3))
83 DWID=DWID*LAMB
84 WID=DWID
85 CALL SSSAVE(ISHH,WID,ISHA,IDZ,0,0,0)
86 ENDIF
87C
88C hh -> hl + hl
89C
90 IF(AMHH.GT.2*AMHL) THEN
91 LAMB1=AMHH**2-4.0*AMHL**2
92 TEMP=CBMA*COS(2.0*ALPHA)
93 TEMP=TEMP+2.0*SBMA*SIN(2.0*ALPHA)
94C
95C Now add hh-hl-hl vertex correction
96C
97C The following 8 lines calculate the radiative
98C hh-hl-hl vertex correction including only
99C effects from tops and stop squarks.
100C
101C DTEMPL=3.0*LOG(1.0+(AMTLSS/MTQ)**2)
102C DTEMPL=DTEMPL-2.0*AMTLSS**2/(AMTLSS**2+MTQ**2)
103C DTEMPR=3.0*LOG(1.0+(AMTRSS/MTQ)**2)
104C DTEMPR=DTEMPR-2.0*AMTRSS**2/(AMTRSS**2+MTQ**2)
105C DELHLL=3.0*G2*CW2*(MTQ**4)*SIN(ALPHA)
106C DELHLL=DELHLL*(COS(ALPHA)**2)/(PI**2)
107C DELHLL=DELHLL/(16.0*(AMW**4)*(SIN(BETA))**3)
108C DELHLL=DELHLL*(DTEMPL+DTEMPR)
109C
110C The subroutine SSHL calculates the radiative
111C hh-hl-hl vertex correction including both
112C top & bottom and stop and sbottom squark
113C (non-degenerate with mixing) effects.
114C A-terms and mu=-2m1 are also included.
115C
116 CALL SSDHLL(DELHLL)
117C
118C Note: the variable TEMP in the line below
119C this is the Lagrangian term (as noted on
120C page 27 of Prof. Tata's personal Lagrangian
121C term notes. Thus DELHLL must also be the
122C Lagrangian entry - not the potential entry.
123C The subroutine SSHLL IS set up to yield the
124C the Lagrangian entry. (We must be very careful
125C about the relative sign between TEMP and DELHLL.)
126C
127 DWID=G2*(AMZ**2)*(TEMP+DELHLL)**2
128 DWID=DWID/(128.0*PI*CW2*(AMHH**2))
129 DWID=DWID*SQRT(LAMB1)
130 WID=DWID
131 CALL SSSAVE(ISHH,WID,ISHL,ISHL,0,0,0)
132 ENDIF
133C
134C hh -> ha + ha
135C
136 IF(AMHH.GT.2*AMHA) THEN
137 LAMB1=AMHH**2-4.0*AMHA**2
138 DWID=CBMA*COS(2*BETA)
139C Now add hh-hp-hp vertex correction
140 DELHPP=3.0*G2*CW2*(MTQ**4)*SIN(ALPHA)
141 DELHPP=DELHPP*(COS(BETA)**2)/(16.0*(PI**2))
142 DELHPP=DELHPP/((AMW**4)*(SIN(BETA))**3)
143 DELHPP=DELHPP*LGTST
144 DWID=G2*(AMZ**2)*(DWID+DELHPP)**2
145 DWID=DWID/(128.0*PI*CW2*(AMHH**2))
146 DWID=DWID*SQRT(LAMB1)
147 WID=DWID
148 CALL SSSAVE(ISHH,WID,ISHA,ISHA,0,0,0)
149 ENDIF
150C
151C hh -> hc+ + hc-
152C
153 IF(AMHH.GT.2*AMHC) THEN
154 LAMB1=1.0-4.0*(AMHC**2)/(AMHH**2)
155 DWID=CBMA*COS(2.0*BETA)/(2.0*CW2)
156 DWID=COS(BETA+ALPHA)-DWID
157C Now add hh-hc-hc vertex correction
158 DELHCC=3.0*G2*MTQ**4*SIN(ALPHA)
159 DELHCC=DELHCC/( SIN(BETA)*(DTAN(BETA))**2 )
160 DELHCC=DELHCC/(32.0*PI**2*AMW**4)
161 DELHCC=DELHCC*LGTST
162 DWID=G2*AMW**2*(-DWID+DELHCC)**2
163 DWID=DWID*SQRT(LAMB1)/(16.0*PI*AMHH)
164 WID=DWID
165 CALL SSSAVE(ISHH,WID,ISHC,-ISHC,0,0,0)
166 ENDIF
167C
168C ha -> hl + z
169C
170 IF(AMHA.GT.AMHL+AMZ) THEN
171 MH=AMHA
172 M1=AMHL
173 M2=AMZ
174 LAMB=SSDLAM(MH**2,M1**2,M2**2)
175 DWID=SQRT(G2*CW2)+SQRT(GP2*SW2)
176 DWID=DWID**2*CAB2*SQRT(LAMB)
177 DWID=DWID/(64.0*PI*(AMZ**2)*(AMHA**3))
178 DWID=DWID*LAMB
179 WID=DWID
180 CALL SSSAVE(ISHA,WID,ISHL,IDZ,0,0,0)
181 ENDIF
182C
183C hc+ -> w+ + hl
184C
185 IF(AMHC.GT.AMW+AMHL) THEN
186 MH=AMHC
187 M1=AMW
188 M2=AMHL
189 LAMB=SSDLAM(MH**2,M1**2,M2**2)
190 DWID=G2*CAB2*SQRT(LAMB)
191 DWID=DWID/( 64.0*PI*(AMW**2)*(AMHC**3) )
192 DWID=DWID*LAMB
193 WID=DWID
194 CALL SSSAVE(ISHC,WID,ISHL,IDW,0,0,0)
195 ENDIF
196C
197 RETURN
198 END