]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/gphys/gbrsga.F
Bugfix in AliPoints2Memory
[u/mrichter/AliRoot.git] / GEANT321 / gphys / gbrsga.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:21:22 cernlib
6* Geant
7*
8*
9#include "geant321/pilot.h"
10*CMZ : 3.21/02 29/03/94 15.41.21 by S.Giani
11*-- Author :
12 SUBROUTINE GBRSGA
13C.
14C. ******************************************************************
15C. * *
16C. * Calculates cross-section in current material *
17C. * for discrete(hard) electron BREMSSTRAHLUNG. *
18C. * *
19C. * ==>Called by : GPHYSI *
20C. * Authors G.Patrick, L.Urban ********* *
21C. * *
22C. ******************************************************************
23C.
24#include "geant321/gcbank.inc"
25#include "geant321/gctrak.inc"
26#include "geant321/gcmate.inc"
27#include "geant321/gconsp.inc"
28#include "geant321/gcjloc.inc"
29#include "geant321/gccuts.inc"
30#include "geant321/gcmulo.inc"
31C.
32C. ------------------------------------------------------------------
33C.
34C=======> Electrons & Positrons
35C
36 SIG=0.
37 IF(Z.LT.1.)GO TO 20
38C
39C Calculate mean free path using total cross-section
40C formula of L.Urban (see Write-up)
41C
42 T = ELOW(IEKBIN)
43 IF(JMIXT.EQ.0)THEN
44C
45C element
46C
47 SIG=GBRSGE(Z,T,BCUTE)
48 SIG=AVO*DENS*SIG/A
49 ELSE
50C
51C compound/mixture
52C
53 NLMAT=Q(JMA+11)
54 NLM=IABS(NLMAT)
55 SIG=0.
56 DO 10 I=1,NLM
57 J = JMIXT+NLM+I
58 AA = Q(J-NLM)
59 ZZ = Q(J)
60 WMAT= Q(J+NLM)
61 S = GBRSGE(ZZ,T,BCUTE)
62 S = WMAT*S/AA
63 SIG = SIG+AVO*DENS*S
64 10 CONTINUE
65 ENDIF
66C
67 20 IF(SIG.GT.0.)THEN
68 Q(JBREM+IEKBIN)=1./SIG
69 Q(JBREM+NEK1+IEKBIN)=1./(SIG*GBFSIG(T,BCUTE))
70 ELSE
71 Q(JBREM+IEKBIN)=BIG
72 Q(JBREM+NEK1+IEKBIN)=BIG
73 ENDIF
74C
75C=======> Muons
76C
77 SIG=0.
78 IF(Z.LT.1.)GO TO 40
79C
80C Calculate mean free path using total cross-section
81C formula of L.Urban (see Write-up)
82C
83 IF(T.LT.1.)GO TO 40
84 IF(JMIXT.EQ.0)THEN
85C
86C element
87C
88 SIG=GBRSGM(Z,T,BCUTM)
89 SIG=AVO*DENS*SIG/A
90 ELSE
91C
92C compound/mixture
93C
94 NLMAT=Q(JMA+11)
95 NLM=IABS(NLMAT)
96 SIG=0.
97 DO 30 I=1,NLM
98 J = JMIXT+NLM+I
99 AA = Q(J-NLM)
100 ZZ = Q(J)
101 WMAT= Q(J+NLM)
102 S = GBRSGM(ZZ,T,BCUTM)
103 S = WMAT*S/AA
104 SIG = SIG+AVO*DENS*S
105 30 CONTINUE
106 ENDIF
107C
108 40 IF(SIG.GT.0.)THEN
109 Q(JBREM+IEKBIN+2*NEK1)=1./SIG
110 ELSE
111 Q(JBREM+IEKBIN+2*NEK1)=BIG
112 ENDIF
113C
114 END