]> git.uio.no Git - u/mrichter/AliRoot.git/blob - ISAJET/code/ssfel.F
Bug in V0A fixed (Guillermo)
[u/mrichter/AliRoot.git] / ISAJET / code / ssfel.F
1 #include "isajet/pilot.h"
2       FUNCTION SSFEL(X,INIT)
3 C***********************************************************************
4 C* Computes the electron spectrum as a convolution of the beam- and    *
5 C* bremsstrahlung-spectra, including leading-log summation for the lat-*
6 C* ter (in one-loop order), and Chen's approximate expression for the  *
7 C* former. X is the e energy in units of the nominal beam energy, and  *
8 C* BETA is 2 alpha_em / pi (log s/me^2 - 1). If more than 99.5% of all *
9 C* electrons are in the delta-peak, beamstrahlung is ignored. Other-   *
10 C* wise, beamstrahlung is included. In the latter case, the complete   *
11 C* spectrum is computed at the first call (with INIT=1), and fitted in *
12 C* a cubic spline; in later calls (with INIT=0), only the spline is    *
13 C* used. This reduces the necessary amount of CPU time considerably.   *
14 C* This subroutine needs the programs BEAMEL, SIMAU8, and SPLINE.      *
15 C***********************************************************************
16 #if defined(CERNLIB_IMPNONE)
17       IMPLICIT NONE
18 #endif
19 #include "isajet/eepar.inc"
20 #include "isajet/brembm.inc"
21 C
22       REAL X,SSFEL
23       INTEGER INIT
24       REAL Y,XLMM,XL,GAM,RE,XKAPPA,NUCL,NUGAM,NGAM,DC,
25      $DX,TAU(100),C(4,100),XM,Z,RES,SSXINT,Y2,H,S,ESTRUC,Y1
26       INTEGER I
27       SAVE DC,NGAM,C,TAU
28       EXTERNAL FBRBM
29 C
30       IF(INIT.NE.0) THEN
31 C       Compute delta function contribution
32         Y=UPSLON
33         XLMM=SIGZ
34         XLMM = 2*SQRT(3.)*XLMM
35         XL = XLMM*1.E12/.197327
36         GAM = EB/5.11E-4
37         RE = 1./(137.*5.11E-4)
38         XKAPPA = 2./(3.*Y)
39         NUCL = 2.5*Y/(SQRT(3.)*137.**2*GAM*RE)
40         NUGAM = NUCL/SQRT(1.+Y**.6666666)
41         NGAM=.5*NUGAM*XL
42         DC = (1.-EXP(-NGAM))/NGAM
43         SSFEL=0.
44 C       No initialization needed if >.995 included in delta peak
45         IF(DC.GT..995) RETURN
46
47 C  ***  Computation of 'knots'   ***
48
49         DX = .05
50         DO 100 I = 1, 19                              
51  100    TAU(I) = FLOAT(I-1)*DX     
52         DO 110 I = 1, 9                               
53  110    TAU(19+I) = .9 + FLOAT(I)*1.E-2
54         DO 120 I = 1, 5                               
55  120    TAU(28+I) = .99 + FLOAT(I)*1.E-3
56         DO 121 I = 1, 12                              
57  121    TAU(33+I) = .995 + FLOAT(I)*2.5E-4
58         DO 130 I = 1, 20                              
59  130    TAU(45+I) = .998 + FLOAT(I)*1.E-4
60
61 C   ***  Computation of corresponding y-values (electron densities)  ***
62
63         XM = TAU(65)
64         DO 140 I = 1,65
65         Z = TAU(I)
66         XMIN = Z
67         RES=SSXINT(Z,FBRBM,XM)
68 140     C(1,I) = RES +DC*ESTRUC(Z,QSQBM)
69
70 C   ***  Computation of derivative at zero   ***
71
72         Z = 1.E-5
73         XMIN = Z
74         RES=SSXINT(Z,FBRBM,XM)
75         Y1 = RES + DC*ESTRUC(Z,QSQBM)
76         Z = 1.E-4
77         XMIN = Z
78         RES=SSXINT(Z,FBRBM,XM)
79         Y2 = RES + DC*ESTRUC(Z,QSQBM)
80         C(1,2) = (Y2-Y1)/(1.E-4 - 1.E-5)
81 147     CALL SPLINE(TAU,C,65,1,0)
82         RETURN
83       ENDIF
84       IF(X.GT..999999) THEN
85         Z = .999999
86       ELSE
87         Z = X
88       ENDIF
89       DC = (1.-EXP(-NGAM))/NGAM
90       IF(DC.GT..995) THEN
91         SSFEL = DC*ESTRUC(Z,QSQBM)
92         RETURN
93       ENDIF
94
95       DO 2 I = 1, 64
96     2 IF(Z.LT.TAU(I+1)) GOTO 3
97     3 H = Z - TAU(I)
98       S = C(1,I) + H * ( C(2,I) + H*(C(3,I)+H*C(4,I)) )
99       SSFEL = S
100       RETURN
101       END