]> git.uio.no Git - u/mrichter/AliRoot.git/blob - HIJING/hipyset1_35/pytest_hijing.F
New Clusterization by IHEP (yuri)
[u/mrichter/AliRoot.git] / HIJING / hipyset1_35 / pytest_hijing.F
1 * $Id$
2     
3 *********************************************************************** 
4     
5       SUBROUTINE PYTEST_HIJING(MTEST)  
6     
7 C...Purpose: to provide a simple program (disguised as a subroutine) to 
8 C...run at installation as a check that the program works as intended.  
9 #include "lujets_hijing.inc"
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     
16 C...Common initial values. Loop over initiating conditions. 
17       MSTP(122)=1   
18       IF(MTEST.LE.0) MSTP(122)=0    
19       MDCY(LUCOMP_HIJING(111),1)=0 
20       NERR=0    
21       DO 130 IPROC=1,7  
22     
23 C...Reset process type, kinematics cuts, and the flags used.    
24       MSEL=0    
25       DO 100 ISUB=1,200 
26   100 MSUB(ISUB)=0  
27       CKIN(1)=2.    
28       CKIN(3)=0.    
29       MSTP(2)=1 
30       MSTP(33)=0    
31       MSTP(81)=1    
32       MSTP(82)=1    
33       MSTP(111)=1   
34       MSTP(131)=0   
35       MSTP(133)=0   
36       PARP(131)=0.01    
37     
38 C...Prompt photon production at fixed target.   
39       IF(IPROC.EQ.1) THEN   
40         PZSUM=300.  
41         PESUM=SQRT(PZSUM**2+ULMASS_HIJING(211)**2)+ULMASS_HIJING(2212)    
42         PQSUM=2.    
43         MSEL=10 
44         CKIN(3)=5.  
45         CALL PYINIT_HIJING('FIXT','pi+','p',PZSUM) 
46     
47 C...QCD processes at ISR energies.  
48       ELSEIF(IPROC.EQ.2) THEN   
49         PESUM=63.   
50         PZSUM=0.    
51         PQSUM=2.    
52         MSEL=1  
53         CKIN(3)=5.  
54         CALL PYINIT_HIJING('CMS','p','p',PESUM)    
55     
56 C...W production + multiple interactions at CERN Collider.  
57       ELSEIF(IPROC.EQ.3) THEN   
58         PESUM=630.  
59         PZSUM=0.    
60         PQSUM=0.    
61         MSEL=12 
62         CKIN(1)=20. 
63         MSTP(82)=4  
64         MSTP(2)=2   
65         MSTP(33)=3  
66         CALL PYINIT_HIJING('CMS','p','pbar',PESUM) 
67     
68 C...W/Z gauge boson pairs + overlayed events at the Tevatron.   
69       ELSEIF(IPROC.EQ.4) THEN   
70         PESUM=1800. 
71         PZSUM=0.    
72         PQSUM=0.    
73         MSUB(22)=1  
74         MSUB(23)=1  
75         MSUB(25)=1  
76         CKIN(1)=200.    
77         MSTP(111)=0 
78         MSTP(131)=1 
79         MSTP(133)=2 
80         PARP(131)=0.04  
81         CALL PYINIT_HIJING('CMS','p','pbar',PESUM) 
82     
83 C...Higgs production at LHC.    
84       ELSEIF(IPROC.EQ.5) THEN   
85         PESUM=17000.    
86         PZSUM=0.    
87         PQSUM=0.    
88         MSEL=16 
89         PMAS(25,1)=300. 
90         CKIN(1)=200.    
91         MSTP(81)=0  
92         MSTP(111)=0 
93         CALL PYINIT_HIJING('CMS','p','pbar',PESUM) 
94     
95 C...Z' production at SSC.   
96       ELSEIF(IPROC.EQ.6) THEN   
97         PESUM=40000.    
98         PZSUM=0.    
99         PQSUM=0.    
100         MSEL=21 
101         PMAS(32,1)=600. 
102         CKIN(1)=400.    
103         MSTP(81)=0  
104         MSTP(111)=0 
105         CALL PYINIT_HIJING('CMS','p','pbar',PESUM) 
106     
107 C...W pair production at 1 TeV e+e- collider.   
108       ELSEIF(IPROC.EQ.7) THEN   
109         PESUM=1000. 
110         PZSUM=0.    
111         PQSUM=0.    
112         MSUB(25)=1  
113         CALL PYINIT_HIJING('CMS','e+','e-',PESUM)  
114       ENDIF 
115     
116 C...Generate 20 events of each required type.   
117       DO 120 IEV=1,20   
118       CALL PYTHIA_HIJING   
119       PESUMM=PESUM  
120       IF(IPROC.EQ.4) PESUMM=MSTI(41)*PESUM  
121     
122 C...Check conservation of energy/momentum/flavour.  
123       MERR=0    
124       DEVE=ABS(PLU_HIJING(0,4)-PESUMM)+ABS(PLU_HIJING(0,3)-PZSUM) 
125       DEVT=ABS(PLU_HIJING(0,1))+ABS(PLU_HIJING(0,2))  
126       DEVQ=ABS(PLU_HIJING(0,6)-PQSUM)  
127       IF(DEVE.GT.1E-3*PESUM.OR.DEVT.GT.MAX(0.01,1E-5*PESUM).OR. 
128      &DEVQ.GT.0.1) MERR=1   
129       IF(MERR.NE.0) WRITE(MSTU(11),1000) IPROC,IEV  
130     
131 C...Check that all KF codes are known ones, and that partons/particles  
132 C...satisfy energy-momentum-mass relation.  
133       DO 110 I=1,N  
134       IF(K(I,1).GT.20) GOTO 110 
135       IF(LUCOMP_HIJING(K(I,2)).EQ.0) THEN  
136         WRITE(MSTU(11),1100) I  
137         MERR=MERR+1 
138       ENDIF 
139       PD=P(I,4)**2-P(I,1)**2-P(I,2)**2-P(I,3)**2-P(I,5)**2* 
140      &SIGN(1.,P(I,5))   
141       IF(ABS(PD).GT.MAX(0.1,0.002*P(I,4)**2,0.002*P(I,5)**2).OR.    
142      &(P(I,5).GE.0..AND.P(I,4).LT.0.)) THEN 
143         WRITE(MSTU(11),1200) I  
144         MERR=MERR+1 
145       ENDIF 
146   110 CONTINUE  
147     
148 C...Listing of erronoeus events, and first event of each type.  
149       IF(MERR.GE.1) NERR=NERR+1 
150       IF(NERR.GE.10) THEN   
151         WRITE(MSTU(11),1300)    
152         CALL LULIST_HIJING(1)  
153         STOP    
154       ENDIF 
155       IF(MTEST.GE.1.AND.(MERR.GE.1.OR.IEV.EQ.1)) THEN   
156         IF(MERR.GE.1) WRITE(MSTU(11),1400)  
157         CALL LULIST_HIJING(1)  
158       ENDIF 
159   120 CONTINUE  
160     
161 C...List statistics for each process type.  
162       IF(MTEST.GE.1) CALL PYSTAT_HIJING(1) 
163   130 CONTINUE  
164     
165 C...Summarize result of run.    
166       IF(NERR.EQ.0) WRITE(MSTU(11),1500)    
167       IF(NERR.GT.0) WRITE(MSTU(11),1600) NERR   
168       RETURN    
169     
170 C...Formats for information.    
171  1000 FORMAT(/5X,'Energy/momentum/flavour nonconservation for process', 
172      &I2,', event',I4)  
173  1100 FORMAT(/5X,'Entry no.',I4,' in following event not known code')   
174  1200 FORMAT(/5X,'Entry no.',I4,' in following event has faulty ',  
175      &'kinematics') 
176  1300 FORMAT(/5X,'This is the tenth error experienced! Something is ',  
177      &'wrong.'/5X,'Execution will be stopped after listing of event.')  
178  1400 FORMAT(5X,'Faulty event follows:')    
179  1500 FORMAT(//5X,'End result of run: no errors detected.') 
180  1600 FORMAT(//5X,'End result of run:',I2,' errors detected.'/  
181      &5X,'This should not have happened!')  
182       END