]> git.uio.no Git - u/mrichter/AliRoot.git/blob - ISAJET/code/ebeam.F
Message commented out
[u/mrichter/AliRoot.git] / ISAJET / code / ebeam.F
1 #include "isajet/pilot.h"
2       FUNCTION EBEAM(X,E)
3 C***********************************************************************
4 C* Modified from contributed subroutine by M. Drees (1/8/99)
5 C* Computes the effective single elctrn spectrum from beamstrahlung at *
6 C* e+e- colliders, using Chen's approximate expressions, for a given   *
7 C* beamstrahlung  parameter Y; is supposed to work for Y <= 10 or so.  *
8 C* The quantities in the COMMON block are the beamstrahlungs parameter *
9 C* Y, the bunch length XL in GeV, the number of photons NGAM, and the  *
10 C* parameters NUCL, NUGAM, W, XKAPPA defined by Chen, as well as the   *
11 C* pre-factor FAC. Y, E and XLMM are read in by BEAM when it is called *
12 C* for the first time, with INIT=1; in this first run the other para-  *
13 C* meters are then computed, and simply used in later calls with       *
14 C* INIT = 0. This COMMON block should be present in the main program   *
15 C* in order to guarantee the survival of these parameters. Finally, X  *
16 C* is the electron energy in units of the nominal beam energy. Notice  *
17 C* that BEAMEL is only the part which is NOT proportional to           *
18 C* delta(1-X); the coefficient of the delta-function is simply         *
19 C* (1-exp(-NGAM))/NGAM.                                                *
20 C***********************************************************************
21 #if defined(CERNLIB_IMPNONE)
22       IMPLICIT NONE
23 #endif
24 #include "isajet/eepar.inc"
25 C
26       REAL XLMM,XL,GAM,RE,XKAPPA,NUCL,NUGAM,NGAM,X,NUBAR,
27      $ETA,EPS,HFAC,RAT,MTERM,TERM,HBAR,XN,EBEAM,Y,E,GAMMA
28       DOUBLE PRECISION DINCGM
29 C
30       Y=UPSLON
31       XLMM=SIGZ
32       XLMM = 2.E0*SQRT(3.E0)*XLMM
33       XL = XLMM*1.E12/.197327E0
34       GAM = E/5.11E-4
35       RE = 1.E0/(137.E0*5.11E-4)
36       XKAPPA = 2.E0/(3.E0*Y)
37       NUCL = 2.5E0*Y/(SQRT(3.E0)*137.E0**2*GAM*RE)
38       NUGAM = NUCL/SQRT(1.E0+Y**.6666666E0)
39       NGAM = .5E0*NUGAM*XL
40       IF(X.LT.1.E-5) X=1.E-5
41       IF(X.GT..99999) X=.99999
42       NUBAR = X*NUCL + (1.0-X)*NUGAM
43       ETA = XKAPPA*(1.0/X-1.0)
44       IF(ETA.GT.5.E1) THEN
45         EBEAM = 1.E-20
46         RETURN
47       ENDIF
48       EPS = 1.E-4
49       HFAC = EXP(-ETA)/(NGAM*(1.E0-X))
50       IF(HFAC.LT.1.E0) EPS = EPS/SQRT(HFAC)
51       RAT = NUBAR/NUGAM*(ETA**.33333333E0)
52       MTERM = RAT
53       TERM = MTERM/GAMMA(.33333E0)*DINCGM(2.D0,DBLE(NGAM),DBLE(EPS))
54       HBAR = TERM
55       XN = 1.0
56 1     XN = XN+1.0
57       MTERM = MTERM*RAT/XN
58       TERM = MTERM/GAMMA(XN/3.)*
59      $DINCGM(DBLE(XN)+1.D0,DBLE(NGAM),DBLE(EPS))
60       HBAR = HBAR+TERM
61       IF(ABS(TERM/HBAR).GT.EPS) GO TO 1
62       EBEAM = HFAC * HBAR
63       IF(EBEAM.LT.0.) EBEAM = 1.E-20
64       RETURN
65       END