]> git.uio.no Git - u/mrichter/AliRoot.git/blob - PYTHIA/pythia/pytest.F
Forgot to check in this the last time. Some changes in AliL3MemHandler as
[u/mrichter/AliRoot.git] / PYTHIA / pythia / pytest.F
1  
2 C***********************************************************************
3  
4        SUBROUTINE PYTEST(MTEST)
5  
6 C...Purpose: to provide a simple program (disguised as a subroutine) to
7 C...run at installation as a check that the program works as intended.
8       COMMON/LUJETS/N,K(4000,5),P(4000,5),V(4000,5)
9       COMMON/LUDAT1/MSTU(200),PARU(200),MSTJ(200),PARJ(200)
10       COMMON/LUDAT2/KCHG(500,3),PMAS(500,4),PARF(2000),VCKM(4,4)
11       COMMON/LUDAT3/MDCY(500,3),MDME(2000,2),BRAT(2000),KFDP(2000,5)
12       COMMON/PYSUBS/MSEL,MSUB(200),KFIN(2,-40:40),CKIN(200)
13       COMMON/PYPARS/MSTP(200),PARP(200),MSTI(200),PARI(200)
14       SAVE /LUJETS/,/LUDAT1/,/LUDAT2/,/LUDAT3/
15       SAVE /PYSUBS/,/PYPARS/
16  
17 C...Common initial values. Loop over initiating conditions.
18       MSTP(122)=MAX(0,MIN(2,MTEST))
19       MDCY(LUCOMP(111),1)=0
20       NERR=0
21       DO 130 IPROC=1,8
22  
23 C...Reset process type, kinematics cuts, and the flags used.
24       MSEL=0
25       DO 100 ISUB=1,200
26       MSUB(ISUB)=0
27   100 CONTINUE
28       CKIN(1)=2.
29       CKIN(3)=0.
30       MSTP(2)=1
31       MSTP(11)=0
32       MSTP(33)=0
33       MSTP(81)=1
34       MSTP(82)=1
35       MSTP(111)=1
36       MSTP(131)=0
37       MSTP(133)=0
38       PARP(131)=0.01
39  
40 C...Prompt photon production at fixed target.
41       IF(IPROC.EQ.1) THEN
42         PZSUM=300.
43         PESUM=SQRT(PZSUM**2+ULMASS(211)**2)+ULMASS(2212)
44         PQSUM=2.
45         MSEL=10
46         CKIN(3)=5.
47         CALL PYINIT('FIXT','pi+','p',PZSUM)
48  
49 C...QCD processes at ISR energies.
50       ELSEIF(IPROC.EQ.2) THEN
51         PESUM=63.
52         PZSUM=0.
53         PQSUM=2.
54         MSEL=1
55         CKIN(3)=5.
56         CALL PYINIT('CMS','p','p',PESUM)
57  
58 C...W production + multiple interactions at CERN Collider.
59       ELSEIF(IPROC.EQ.3) THEN
60         PESUM=630.
61         PZSUM=0.
62         PQSUM=0.
63         MSEL=12
64         CKIN(1)=20.
65         MSTP(82)=4
66         MSTP(2)=2
67         MSTP(33)=3
68         CALL PYINIT('CMS','p','pbar',PESUM)
69  
70 C...W/Z gauge boson pairs + pileup events at the Tevatron.
71       ELSEIF(IPROC.EQ.4) THEN
72         PESUM=1800.
73         PZSUM=0.
74         PQSUM=0.
75         MSUB(22)=1
76         MSUB(23)=1
77         MSUB(25)=1
78         CKIN(1)=200.
79         MSTP(111)=0
80         MSTP(131)=1
81         MSTP(133)=2
82         PARP(131)=0.04
83         CALL PYINIT('CMS','p','pbar',PESUM)
84  
85 C...Higgs production at LHC.
86       ELSEIF(IPROC.EQ.5) THEN
87         PESUM=15400.
88         PZSUM=0.
89         PQSUM=2.
90         MSUB(3)=1
91         MSUB(102)=1
92         MSUB(123)=1
93         MSUB(124)=1
94         PMAS(25,1)=300.
95         CKIN(1)=200.
96         MSTP(81)=0
97         MSTP(111)=0
98         CALL PYINIT('CMS','p','p',PESUM)
99  
100 C...Z' production at SSC.
101       ELSEIF(IPROC.EQ.6) THEN
102         PESUM=40000.
103         PZSUM=0.
104         PQSUM=2.
105         MSEL=21
106         PMAS(32,1)=600.
107         CKIN(1)=400.
108         MSTP(81)=0
109         MSTP(111)=0
110         CALL PYINIT('CMS','p','p',PESUM)
111  
112 C...W pair production at 1 TeV e+e- collider.
113       ELSEIF(IPROC.EQ.7) THEN
114         PESUM=1000.
115         PZSUM=0.
116         PQSUM=0.
117         MSUB(25)=1
118         MSUB(69)=1
119         MSTP(11)=1
120         CALL PYINIT('CMS','e+','e-',PESUM)
121  
122 C...Deep inelastic scattering at a LEP+LHC ep collider.
123       ELSEIF(IPROC.EQ.8) THEN
124         P(1,1)=0.
125         P(1,2)=0.
126         P(1,3)=8000.
127         P(2,1)=0.
128         P(2,2)=0.
129         P(2,3)=-80.
130         PESUM=8080.
131         PZSUM=7920.
132         PQSUM=0.
133         MSUB(10)=1
134         CKIN(3)=50.
135         MSTP(111)=0
136         CALL PYINIT('USER','p','e-',PESUM)
137       ENDIF
138  
139 C...Generate 20 events of each required type.
140       DO 120 IEV=1,20
141       CALL PYEVNT
142       PESUMM=PESUM
143       IF(IPROC.EQ.4) PESUMM=MSTI(41)*PESUM
144  
145 C...Check conservation of energy/momentum/flavour.
146       MERR=0
147       DEVE=ABS(PLU(0,4)-PESUMM)+ABS(PLU(0,3)-PZSUM)
148       DEVT=ABS(PLU(0,1))+ABS(PLU(0,2))
149       DEVQ=ABS(PLU(0,6)-PQSUM)
150       IF(DEVE.GT.2E-3*PESUM.OR.DEVT.GT.MAX(0.01,1E-4*PESUM).OR.
151      &DEVQ.GT.0.1) MERR=1
152       IF(MERR.NE.0) WRITE(MSTU(11),5000) IPROC,IEV
153  
154 C...Check that all KF codes are known ones, and that partons/particles
155 C...satisfy energy-momentum-mass relation.
156       DO 110 I=1,N
157       IF(K(I,1).GT.20) GOTO 110
158       IF(LUCOMP(K(I,2)).EQ.0) THEN
159         WRITE(MSTU(11),5100) I
160         MERR=MERR+1
161       ENDIF
162       PD=P(I,4)**2-P(I,1)**2-P(I,2)**2-P(I,3)**2-P(I,5)**2*
163      &SIGN(1.,P(I,5))
164       IF(ABS(PD).GT.MAX(0.1,0.002*P(I,4)**2,0.002*P(I,5)**2).OR.
165      &(P(I,5).GE.0..AND.P(I,4).LT.0.)) THEN
166         WRITE(MSTU(11),5200) I
167         MERR=MERR+1
168       ENDIF
169   110 CONTINUE
170  
171 C...Listing of erroneous events, and first event of each type.
172       IF(MERR.GE.1) NERR=NERR+1
173       IF(NERR.GE.10) THEN
174         WRITE(MSTU(11),5300)
175         CALL LULIST(1)
176         STOP
177       ENDIF
178       IF(MTEST.GE.1.AND.(MERR.GE.1.OR.IEV.EQ.1)) THEN
179         IF(MERR.GE.1) WRITE(MSTU(11),5400)
180         CALL LULIST(1)
181       ENDIF
182   120 CONTINUE
183  
184 C...List statistics for each process type.
185       IF(MTEST.GE.1) CALL PYSTAT(1)
186   130 CONTINUE
187  
188 C...Summarize result of run.
189       IF(NERR.EQ.0) WRITE(MSTU(11),5500)
190       IF(NERR.GT.0) WRITE(MSTU(11),5600) NERR
191       RETURN
192  
193 C...Formats for information.
194  5000 FORMAT(/5X,'Energy/momentum/flavour nonconservation for process',
195      &I2,', event',I4)
196  5100 FORMAT(/5X,'Entry no.',I4,' in following event not known code')
197  5200 FORMAT(/5X,'Entry no.',I4,' in following event has faulty ',
198      &'kinematics')
199  5300 FORMAT(/5X,'This is the tenth error experienced! Something is ',
200      &'wrong.'/5X,'Execution will be stopped after listing of event.')
201  5400 FORMAT(5X,'Faulty event follows:')
202  5500 FORMAT(//5X,'End result of PYTEST: no errors detected.')
203  5600 FORMAT(//5X,'End result of PYTEST:',I2,' errors detected.'/
204      &5X,'This should not have happened!')
205       END