]> git.uio.no Git - u/mrichter/AliRoot.git/blob - HIJING/hipyset1_35/pyinre_hijing.F
Updated VZERO source
[u/mrichter/AliRoot.git] / HIJING / hipyset1_35 / pyinre_hijing.F
1 * $Id$
2     
3 C*********************************************************************  
4     
5       SUBROUTINE PYINRE_HIJING 
6     
7 C...Calculates full and effective widths of guage bosons, stores masses 
8 C...and widths, rescales coefficients to be used for resonance  
9 C...production generation.  
10 #include "ludat1_hijing.inc"
11 #include "ludat2_hijing.inc"
12 #include "ludat3_hijing.inc"
13 #include "pysubs_hijing.inc"
14 #include "pypars_hijing.inc"
15 #include "pyint1_hijing.inc"
16 #include "pyint2_hijing.inc"
17 #include "pyint4_hijing.inc"
18 #include "pyint6_hijing.inc"
19       DIMENSION WDTP(0:40),WDTE(0:40,0:5)   
20     
21 C...Calculate full and effective widths of gauge bosons.    
22       AEM=PARU(101) 
23       XW=PARU(102)  
24       DO 100 I=21,40    
25       DO 100 J=0,40 
26       WIDP(I,J)=0.  
27   100 WIDE(I,J)=0.  
28     
29 C...W+/-:   
30       WMAS=PMAS(24,1)   
31       WFAC=AEM/(24.*XW)*WMAS    
32       CALL PYWIDT_HIJING(24,WMAS,WDTP,WDTE)    
33       WIDS(24,1)=((WDTE(0,1)+WDTE(0,2))*(WDTE(0,1)+WDTE(0,3))+  
34      &(WDTE(0,1)+WDTE(0,2)+WDTE(0,1)+WDTE(0,3))*(WDTE(0,4)+WDTE(0,5))+  
35      &2.*WDTE(0,4)*WDTE(0,5))/WDTP(0)**2    
36       WIDS(24,2)=(WDTE(0,1)+WDTE(0,2)+WDTE(0,4))/WDTP(0)    
37       WIDS(24,3)=(WDTE(0,1)+WDTE(0,3)+WDTE(0,4))/WDTP(0)    
38       DO 110 I=0,40 
39       WIDP(24,I)=WFAC*WDTP(I)   
40   110 WIDE(24,I)=WFAC*WDTE(I,0) 
41     
42 C...H+/-:   
43       HCMAS=PMAS(37,1)  
44       HCFAC=AEM/(8.*XW)*(HCMAS/WMAS)**2*HCMAS   
45       CALL PYWIDT_HIJING(37,HCMAS,WDTP,WDTE)   
46       WIDS(37,1)=((WDTE(0,1)+WDTE(0,2))*(WDTE(0,1)+WDTE(0,3))+  
47      &(WDTE(0,1)+WDTE(0,2)+WDTE(0,1)+WDTE(0,3))*(WDTE(0,4)+WDTE(0,5))+  
48      &2.*WDTE(0,4)*WDTE(0,5))/WDTP(0)**2    
49       WIDS(37,2)=(WDTE(0,1)+WDTE(0,2)+WDTE(0,4))/WDTP(0)    
50       WIDS(37,3)=(WDTE(0,1)+WDTE(0,3)+WDTE(0,4))/WDTP(0)    
51       DO 120 I=0,40 
52       WIDP(37,I)=HCFAC*WDTP(I)  
53   120 WIDE(37,I)=HCFAC*WDTE(I,0)    
54     
55 C...Z0: 
56       ZMAS=PMAS(23,1)   
57       ZFAC=AEM/(48.*XW*(1.-XW))*ZMAS    
58       CALL PYWIDT_HIJING(23,ZMAS,WDTP,WDTE)    
59       WIDS(23,1)=((WDTE(0,1)+WDTE(0,2))**2+ 
60      &2.*(WDTE(0,1)+WDTE(0,2))*(WDTE(0,4)+WDTE(0,5))+   
61      &2.*WDTE(0,4)*WDTE(0,5))/WDTP(0)**2    
62       WIDS(23,2)=(WDTE(0,1)+WDTE(0,2)+WDTE(0,4))/WDTP(0)    
63       WIDS(23,3)=0. 
64       DO 130 I=0,40 
65       WIDP(23,I)=ZFAC*WDTP(I)   
66   130 WIDE(23,I)=ZFAC*WDTE(I,0) 
67     
68 C...H0: 
69       HMAS=PMAS(25,1)   
70       HFAC=AEM/(8.*XW)*(HMAS/WMAS)**2*HMAS  
71       CALL PYWIDT_HIJING(25,HMAS,WDTP,WDTE)    
72       WIDS(25,1)=((WDTE(0,1)+WDTE(0,2))**2+ 
73      &2.*(WDTE(0,1)+WDTE(0,2))*(WDTE(0,4)+WDTE(0,5))+   
74      &2.*WDTE(0,4)*WDTE(0,5))/WDTP(0)**2    
75       WIDS(25,2)=(WDTE(0,1)+WDTE(0,2)+WDTE(0,4))/WDTP(0)    
76       WIDS(25,3)=0. 
77       DO 140 I=0,40 
78       WIDP(25,I)=HFAC*WDTP(I)   
79   140 WIDE(25,I)=HFAC*WDTE(I,0) 
80     
81 C...Z'0:    
82       ZPMAS=PMAS(32,1)  
83       ZPFAC=AEM/(48.*XW*(1.-XW))*ZPMAS  
84       CALL PYWIDT_HIJING(32,ZPMAS,WDTP,WDTE)   
85       WIDS(32,1)=((WDTE(0,1)+WDTE(0,2)+WDTE(0,3))**2+   
86      &2.*(WDTE(0,1)+WDTE(0,2))*(WDTE(0,4)+WDTE(0,5))+   
87      &2.*WDTE(0,4)*WDTE(0,5))/WDTP(0)**2    
88       WIDS(32,2)=(WDTE(0,1)+WDTE(0,2)+WDTE(0,4))/WDTP(0)    
89       WIDS(32,3)=0. 
90       DO 150 I=0,40 
91       WIDP(32,I)=ZPFAC*WDTP(I)  
92   150 WIDE(32,I)=ZPFAC*WDTE(I,0)    
93     
94 C...R:  
95       RMAS=PMAS(40,1)   
96       RFAC=0.08*RMAS/((MSTP(1)-1)*(1.+6.*(1.+ULALPS_HIJING(RMAS**2)
97      $     /PARU(1)))) 
98       CALL PYWIDT_HIJING(40,RMAS,WDTP,WDTE)    
99       WIDS(40,1)=((WDTE(0,1)+WDTE(0,2))*(WDTE(0,1)+WDTE(0,3))+  
100      &(WDTE(0,1)+WDTE(0,2)+WDTE(0,1)+WDTE(0,3))*(WDTE(0,4)+WDTE(0,5))+  
101      &2.*WDTE(0,4)*WDTE(0,5))/WDTP(0)**2    
102       WIDS(40,2)=(WDTE(0,1)+WDTE(0,2)+WDTE(0,4))/WDTP(0)    
103       WIDS(40,3)=(WDTE(0,1)+WDTE(0,3)+WDTE(0,4))/WDTP(0)    
104       DO 160 I=0,40 
105       WIDP(40,I)=WFAC*WDTP(I)   
106   160 WIDE(40,I)=WFAC*WDTE(I,0) 
107     
108 C...Q:  
109       KFLQM=1   
110       DO 170 I=1,MIN(8,MDCY(21,3))  
111       IDC=I+MDCY(21,2)-1    
112       IF(MDME(IDC,1).LE.0) GOTO 170 
113       KFLQM=I   
114   170 CONTINUE  
115       MINT(46)=KFLQM    
116       KFPR(81,1)=KFLQM  
117       KFPR(81,2)=KFLQM  
118       KFPR(82,1)=KFLQM  
119       KFPR(82,2)=KFLQM  
120     
121 C...Set resonance widths and branching ratios in JETSET.    
122       DO 180 I=1,6  
123       IF(I.LE.3) KC=I+22    
124       IF(I.EQ.4) KC=32  
125       IF(I.EQ.5) KC=37  
126       IF(I.EQ.6) KC=40  
127       PMAS(KC,2)=WIDP(KC,0) 
128       PMAS(KC,3)=MIN(0.9*PMAS(KC,1),10.*PMAS(KC,2)) 
129       DO 180 J=1,MDCY(KC,3) 
130       IDC=J+MDCY(KC,2)-1    
131       BRAT(IDC)=WIDE(KC,J)/WIDE(KC,0)   
132   180 CONTINUE  
133     
134 C...Special cases in treatment of gamma*/Z0: redefine process name. 
135       IF(MSTP(43).EQ.1) THEN    
136         PROC(1)='f + fb -> gamma*'  
137       ELSEIF(MSTP(43).EQ.2) THEN    
138         PROC(1)='f + fb -> Z0'  
139       ELSEIF(MSTP(43).EQ.3) THEN    
140         PROC(1)='f + fb -> gamma*/Z0'   
141       ENDIF 
142     
143 C...Special cases in treatment of gamma*/Z0/Z'0: redefine process name. 
144       IF(MSTP(44).EQ.1) THEN    
145         PROC(141)='f + fb -> gamma*'    
146       ELSEIF(MSTP(44).EQ.2) THEN    
147         PROC(141)='f + fb -> Z0'    
148       ELSEIF(MSTP(44).EQ.3) THEN    
149         PROC(141)='f + fb -> Z''0'  
150       ELSEIF(MSTP(44).EQ.4) THEN    
151         PROC(141)='f + fb -> gamma*/Z0' 
152       ELSEIF(MSTP(44).EQ.5) THEN    
153         PROC(141)='f + fb -> gamma*/Z''0'   
154       ELSEIF(MSTP(44).EQ.6) THEN    
155         PROC(141)='f + fb -> Z0/Z''0'   
156       ELSEIF(MSTP(44).EQ.7) THEN    
157         PROC(141)='f + fb -> gamma*/Z0/Z''0'    
158       ENDIF 
159     
160       RETURN    
161       END