]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/gphys/gsynge.F
New configurale version.
[u/mrichter/AliRoot.git] / GEANT321 / gphys / gsynge.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:21:34 cernlib
6* Geant
7*
8*
9#include "geant321/pilot.h"
10*CMZ : 3.21/02 29/03/94 15.41.23 by S.Giani
11*-- Author :
12 SUBROUTINE GSYNGE (GAMMA,AM,HKGAUS,STEP,NTR,ETR,STR)
13C
14C. ******************************************************************
15C. * *
16C. * Generation of synchrotron radiation photons: *
17C. * o sample the number of generated photons from *
18C. * Poisson distribution *
19C. * o sample the energy of each photon from the *
20C. * tables below (these numbers can be computed by *
21C. * the routine GSYNIT) *
22C. * YT(I) = photon energy/ critical photon energy (e/ec) *
23C. * FTI(I) = int from YT(I) to inf (20) of dN**2/dxde *
24C. * where dN**2/dxde = int from e/ec to inf of *
25C. * K_5/3(x) dx *
26C. * *
27C. * GAMMA - Lorentz factor, *
28C. * H - transverse component of the magnetic field *
29C. * to particle direction, *
30C. * STEP - current step in magnetic field, *
31C. * NTR - number of the synchrotron photons, *
32C. * ETR(k) - photon energy, *
33C. * STR(k) - photon coordinate. *
34C. * *
35C. * ==> Called by : GSYNC *
36C. * Authors : Igor Gavrilenko *
37C. * *
38C. ******************************************************************
39C
40C
41#include "geant321/gcunit.inc"
42#if defined(CERNLIB_NEVER)
43 COMMON /SYNTAB / YT(54),FT(53),FTI(53)
44#endif
45C...
46 DIMENSION ETR(100),STR(100),RNDM(200)
47#if !defined(CERNLIB_NEVER)
48 DIMENSION YT(54),FTI(53)
49#endif
50C...
51 DATA FTI/0.9827082157, 0.9756910801, 0.9708271027, 0.9669673443,
52 + 0.9637124538, 0.9608694911, 0.9583284855, 0.9560201764,
53 + 0.9538975954, 0.9519274235, 0.9368366003, 0.9263846874,
54 + 0.9180962443, 0.9111109376, 0.9050130844, 0.8995658755,
55 + 0.8946199417, 0.8900741935, 0.8858568072, 0.8536163568,
56 + 0.8313701749, 0.8137849569, 0.7990072370, 0.7861415148,
57 + 0.7746775150, 0.7642934322, 0.7547715902, 0.7459571362,
58 + 0.6792119741, 0.6339961290, 0.5988188982, 0.5696868896,
59 + 0.5446703434, 0.5226698518, 0.5029919147, 0.4851673245,
60 + 0.4688622653, 0.3516088724, 0.2802021503, 0.2298262119,
61 + 0.1918447465, 0.1620831937, 0.1381656080, 0.1185975820,
62 + 0.1023733467, 0.8878208697E-01, 0.2343492396E-01,
63 + 0.7047536317E-02, 0.2237016102E-02, 0.7283322047E-03,
64 + 0.2375631739E-03, 0.7417966117E-04, 0.1891316060E-04/
65
66 DATA YT/1E-5,2E-5,3E-5,4E-5,5E-5,6E-5,7E-5,8E-5,9E-5,
67 + 1E-4,2E-4,3E-4,4E-4,5E-4,6E-4,7E-4,8E-4,9E-4,
68 + 1E-3,2E-3,3E-3,4E-3,5E-3,6E-3,7E-3,8E-3,9E-3,
69 + 1E-2,2E-2,3E-2,4E-2,5E-2,6E-2,7E-2,8E-2,9E-2,
70 + .1,.2,.3,.4,.5,.6,.7,.8,.9,1.,2.,3.,4.,5.,6.,7.,8.,9./
71C...
72 NTR = 0
73 H = 0.1*HKGAUS
74 IF(H.LE.0.) GO TO 999
75C...
76 RAD = 333.33*AM*GAMMA/H
77C...
78 EC = 2.96E-8*GAMMA**3/RAD
79C...
80 AN = .01053*GAMMA/RAD*STEP
81 CALL GPOISS(AN,N,1)
82 N=MIN(N,100)
83 IF(N.LE.0) GO TO 999
84C...
85 CALL GRNDM(RNDM,N*2)
86 DO 40 I = 1,N
87 K1 = 1
88 K2 = 53
89 R = RNDM(2*I-1)*(FTI(1)-FTI(53))+FTI(53)
90C...
91 10 K = (K1+K2)/2
92 IF(R.NE.FTI(K)) GO TO 20
93 E = YT(K)*EC
94 GO TO 30
95C...
96 20 IF(R.GT.FTI(K)) THEN
97 K2 = K
98 ELSEIF(R.LT.FTI(K)) THEN
99 K1 = K
100 ENDIF
101 IF(K2-K1.GT.1) GO TO 10
102C...
103 IF(YT(K2).LE.1.) THEN
104 Y2 = LOG(YT(K2))
105 Y1 = LOG(YT(K1))
106 E = Y2+(R-FTI(K2))*(Y1-Y2)/(FTI(K1)-FTI(K2))
107 E = EXP(E)*EC
108 ELSE
109 F2 = LOG(FTI(K2))
110 F1 = LOG(FTI(K1))
111 DR = LOG(R)
112 E = YT(K2)+(DR-F2)*(YT(K1)-YT(K2))/(F1-F2)
113 E = E*EC
114 END IF
115C...
116 30 CONTINUE
117C
118 IF(E/EC.GT.20.) THEN
119 WRITE(CHMAIL,'('' *** GSYNGE: Photons have e>20*ec, e= '',
120 + G10.4,'' keV, ec= '',G10.4,'' keV'')') E,EC
121 CALL GMAIL(1,0)
122 GO TO 40
123 ENDIF
124C...
125 NTR = NTR+1
126 ETR(NTR) = E*1.E-6
127 STR(NTR) = STEP*RNDM(2*I)
128 40 CONTINUE
129C...
130 999 END