]> git.uio.no Git - u/mrichter/AliRoot.git/blame - HERWIG/jimmy/jimmy/hwmsct.F
reset cluster's used flag (Markus)
[u/mrichter/AliRoot.git] / HERWIG / jimmy / jimmy / hwmsct.F
CommitLineData
ef94df36 1 SUBROUTINE HWMSCT(ABORT)
2C -----------------------------------------------------------------
3C Administer multiple scattering
4C
5C If the returned argument (ABORT) is TRUE then the event has been
6C vetoed by the eikonalisation, and should be abandoned.
7C -----------------------------------------------------------------
8#include "herwig65.inc"
9#include "jimmy.inc"
10
11 LOGICAL ABORT
12 INTEGER N, I, J, REPORT, CHECKSUM, CHECKEV, COUNTER
13 INTEGER TMPPR
14 LOGICAL FIRST
15 DATA FIRST /.TRUE./
16 SAVE FIRST, CHECKSUM, CHECKEV
17
18 IF (FIRST) THEN
19 CHECKSUM=0.
20 CHECKEV=0.
21 FIRST=.FALSE.
22 ENDIF
23
24C -- Abort the event if there are any errors.
25 IF (IERROR.NE.0) THEN
26 ABORT=.TRUE.
27 CALL HWUFNE
28 RETURN
29 ENDIF
30
31 ABORT = .FALSE.
32
33C Decide how many hard scatters
34C If NSCAT=0, this event was rejected (this can happen because the
35C cross section at a given centre-of-mass energy changes with
36C eikonalisation).
37C J returns the index of the upper S bound.
38 CALL HWNSCT(J)
39
40 IF (JMBUG.GT.0) THEN
41 WRITE(*,*) 'HWMSCT:NUMBER OF SCATTERS REQUESTED =',NSCAT
42 CHECKSUM=CHECKSUM+NSCAT
43 IF (NSCAT.GT.0) THEN
44 CHECKEV=CHECKEV+1
45 WRITE(*,*) 'RUNNING AVERAGE=',FLOAT(CHECKSUM)/FLOAT(CHECKEV)
46 ENDIF
47 ENDIF
48
49 IF (NSCAT.EQ.0) THEN
50C -- Finish event (making sure aborted events aren't printed)
51 TMPPR=MAXPR
52 MAXPR=0
53 CALL HWUFNE
54 MAXPR=TMPPR
55 ABORT = .TRUE.
56 NEVHEP=NEVHEP-1
57 RETURN
58 ENDIF
59
60 REPORT = 0
61 COUNTER = 0
62 N = NSCAT
63
64 DO I = 2, N
65
66 10 CONTINUE
67
68 IF (REPORT.EQ.0) THEN
69
70 CALL HWHSCT(REPORT,(I.EQ.2),JMUEO,PTJIM)
71
72 IF (REPORT.EQ.5) THEN
73 WRITE(*,*) 'FATAL ERROR'
74 RETURN
75 ENDIF
76
77c If there's an error which isn't a fatal error, retry.
78 IF (REPORT.NE.0) THEN
79
80 IF (JMBUG.GT.0) WRITE(*,*) 'Report=',report
81 REPORT=0
82 IF (COUNTER.LT.MAXMSTRY) THEN
83 COUNTER=COUNTER+1
84 GOTO 10
85 ELSE
86c Avoid infinite loops. If there's really no phase space, reduce
87c the number of scatters.
88 NSCAT=NSCAT-1
89 IF (JMBUG.GT.0) WRITE(*,*) 'LOST A SCATTER'
90 COUNTER=0
91 ENDIF
92 ENDIF
93
94 IF (ANOMOFF) THEN
95
96 IF (ANOMSC(1,1).NE.0.OR.ANOMSC(1,2).NE.0)THEN
97 WRITE(JMOUT,*) 'Anom. scat',ANOMSC(1,1),ANOMSC(1,2)
98 NSCAT=NSCAT-1
99 REPORT=6
100 ENDIF
101
102 ENDIF
103
104 ENDIF
105
106 ENDDO
107
108 IF (JMBUG.GT.0) THEN
109 WRITE(*,*) 'HWMSCT:NUMBER OF SCATTERS GENERATED =',NSCAT
110 ENDIF
111
112 100 CONTINUE
113
114C =====================================================================
115C Store the number of events lost from the HERWIG cross section.
116C (which equals the number of "multiple" scatters)
117 TOTSCAT = TOTSCAT + NSCAT
118 IF (JMUEO.EQ.0) THEN
119 NLOST = NLOST + (NSCAT - 1.D0)
120 ENDIF
121C Get the S-hat distribution correct. To do this we must alter
122C the amount of vetoing of events, as this is based initially on
123C the simple eikonal model without taking into account "lost"
124C scatters.
125C We should decrease the chances of an event being rejected by
126C a factor of NSCAT(S)/N(S) where NSCAT is the number of scatters
127C actually generated at this S, and N(S) is the number that would have
128C been generated so far by the "simple" model.
129C Store these numbers in JMARRY(MAXMS+5,I) and JMARRY(MAXMS+6,I)
130
131c Turn this feature off if the process being generated is not
132c eikonalised itself (i.e. MI are being used only for the
133c underlying event.
134 JMARRY(MAXMS+5,J) = JMARRY(MAXMS+5,J)+FLOAT(NSCAT)
135 JMARRY(MAXMS+6,J) = JMARRY(MAXMS+6,J)+FLOAT(N)
136
137 RETURN
138 END
139
140
141
142