/[PAMELA software]/gpamela/gptrd/gpxtr.F
ViewVC logotype

Annotation of /gpamela/gptrd/gpxtr.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.1 - (hide annotations) (download)
Thu Jul 11 16:02:01 2002 UTC (22 years, 4 months ago) by cafagna
Branch: MAIN
Branch point for: v3r0
Initial revision

1 cafagna 3.1 *
2     * $Id$
3     *
4     * $Log$
5     *
6     *CMZ : 3.00/00 05/02/2002 12.51.38 by Unknown
7     *-- Author : Marialuigia Ambriola 11/05/2001
8     SUBROUTINE GPXTR
9     **************************************************************************
10     * *
11     * Generates and absorbs transition radiation spectrum in TRD *
12     * *
13     * *
14     * *
15     * Called by: GUSTEP *
16     * Author: Marialuigia Ambriola 11/05/2001 *
17     * *
18     **************************************************************************
19     #include "gpgene.inc"
20     #include "gctrak.inc"
21     #include "gctmed.inc"
22     #include "gpmed.inc"
23     #include "gpsed.inc"
24     #include "gcsets.inc"
25     #include "gpaltr.inc"
26     #include "gckine.inc"
27     #include "gcnum.inc"
28     #include "gcflag.inc"
29     #include "gptotr.inc"
30     #include "gcunit.inc"
31     EXTERNAL XTRYIELD
32     EXTERNAL NPOISS
33     EXTERNAL XTRINTER
34     EXTERNAL XTRINTEG
35     REAL CAM,RL,G,NF,WR,CR,SPH,CATT,W,E
36     INTEGER INDEX,INDEXAIR,INDEXC,LAY
37     c centimeter and GeV:
38     DATA RL1/7.0E-4/,RL2/204.E-4/,N/71/,w1/31.59E-9/,w2/.7E-9/
39     DATA IEVOLD/-1/,NTMOLD/-1/
40     PARAMETER (ALPHA=1/137.,PG=3.1415926536,HTC=197.3269E-16)
41     PARAMETER (C=3.E+10)
42     **************
43     *particle inside kapton, radiator or xenon?
44     *if yes, calcolates the length of the track.
45     *NUMED is the number of the tracking medium (common GCTMED)
46     *MTRAD, MKAP and MXE are the numbers of radiator, kapton and xenon
47     *tracking media, like defined by GPAMELA.
48     IF(CHARGE.EQ.0) THEN
49     RETURN
50     ENDIF
51     IF(AMASS.LE.0) THEN
52     WRITE(CHMAIL,10000) AMASS
53     CALL GMAIL(1,0)
54     RETURN
55     ENDIF
56     G=GETOT/AMASS
57     IF(G.LE.100.) THEN
58     RETURN
59     ENDIF
60     IF((NUMED.EQ.MKAP.AND.IDET.EQ.IDTRSO).OR.NUMED.EQ.
61     + MTRAD.OR.NUMED.EQ.MXE) THEN
62     IF(INWVOL.EQ.1.) THEN
63     CAM=SLENG
64     RETURN
65     ELSEIF(INWVOL.EQ.2) THEN
66     C #
67     C # Calculate the layer number
68     C #
69     IF(NUMED.EQ.MXE) THEN
70     IF(NUMBV(NVNAME-1).GE.29.AND.NUMBV(NVNAME-1).LE.32)LAY=2
71     IF(NUMBV(NVNAME-1).GE.25.AND.NUMBV(NVNAME-1).LE.28)LAY=4
72     IF(NUMBV(NVNAME-1).GE.21.AND.NUMBV(NVNAME-1).LE.24)LAY=6
73     IF(NUMBV(NVNAME-1).GE.17.AND.NUMBV(NVNAME-1).LE.20)LAY=8
74     IF(NUMBV(NVNAME-1).GE.13.AND.NUMBV(NVNAME-1).LE.16)LAY=10
75     IF(NUMBV(NVNAME-1).GE.10.AND.NUMBV(NVNAME-1).LE.12)LAY=12
76     IF(NUMBV(NVNAME-1).GE.7.AND.NUMBV(NVNAME-1).LE.9)LAY=14
77     IF(NUMBV(NVNAME-1).GE.4.AND.NUMBV(NVNAME-1).LE.6)LAY=16
78     IF(NUMBV(NVNAME-1).GE.1.AND.NUMBV(NVNAME-1).LE.3)LAY=18
79     IF(NUMBV(NVNAME).GT.16) THEN
80     LAY = LAY - 1
81     ENDIF
82     ENDIF
83     CAM=SLENG-CAM
84     ELSE
85     RETURN
86     ENDIF
87     ELSE
88     RETURN
89     ENDIF
90     ****************
91     INDEX=0
92     INDEXAIR=0
93     INDEXC=0
94     IF(INWVOL.NE.2) RETURN
95     IF(IEVOLD.NE.IEVENT.OR.NTMOLD.NE.NTMULT) THEN
96     CALL VZERO(EY,115)
97     ENDIF
98     IEVOLD=IEVENT
99     NTMOLD=NTMULT
100     SPH=0.
101     NPHTR=0
102     ENPHTR=0.
103     IF(NUMED.EQ.MKAP.AND.IDET.EQ.IDTRSO) INDEX=4
104     IF(NUMED.EQ.MXE) INDEX=3
105     IF(NUMED.EQ.MTRAD) THEN
106     INDEXAIR=1
107     INDEXC=2
108     RL=RL1+RL2
109     ENDIF
110     ****************
111     c radiator:
112     IF(INDEX.EQ.0) THEN
113     NF=CAM/RL
114     DO I=1,115
115     XTREN=XTRYIELD(I,G)
116     WR=0.
117     CR=NF*(ATTTRD(I,INDEXAIR)*RL2+ATTTRD(I,INDEXC)*RL1)
118     IF(CR.GT.0.) WR=EXP(-CR)
119     c considering the whole radiator and the absorption.
120     c when dividing for enatt I consider the number of photons per unit energy,
121     c which are created and transmitted by the radiator.
122     C remember that enatt is in keV unity.
123     IF(CR.GT.0.AND.NF.GT.1) THEN
124     XTREN=2*NF*XTREN*(1.-WR)/(CR*ENATT(I))
125     EY(I)=EY(I)*WR+XTREN
126     SPH=SPH+EY(I)
127     ENDIF
128     ENDDO
129     ENDIF
130     goto 999
131     print*,'index,IEVENT,gamma,spettro'
132     print*,index,IEVENT,g
133     print*,(ey(i),i=1,4)
134     print*,(ey(i),i=5,8)
135     print*,(ey(i),i=9,12)
136     print*,(ey(i),i=13,16)
137     print*,(ey(i),i=17,20)
138     print*,(ey(i),i=21,24)
139     print*,(ey(i),i=25,28)
140     print*,(ey(i),i=29,32)
141     print*,(ey(i),i=33,36)
142     print*,(ey(i),i=37,40)
143     print*,(ey(i),i=41,44)
144     print*,(ey(i),i=45,48)
145     print*,(ey(i),i=49,52)
146     print*,(ey(i),i=53,56)
147     print*,(ey(i),i=57,60)
148     print*,(ey(i),i=61,64)
149     print*,(ey(i),i=65,68)
150     print*,(ey(i),i=69,72)
151     print*,(ey(i),i=73,76)
152     print*,(ey(i),i=77,80)
153     print*,(ey(i),i=81,84)
154     print*,(ey(i),i=85,88)
155     print*,(ey(i),i=89,92)
156     print*,(ey(i),i=93,96)
157     print*,(ey(i),i=97,100)
158     print*,(ey(i),i=101,104)
159     print*,(ey(i),i=105,108)
160     print*,(ey(i),i=109,112)
161     print*,(ey(i),i=113,115)
162     999 continue
163     ******************
164     C now the spectrum is propagated in the other absorbent media in the TRD:
165     c the absorber could be the kapton or the Xe-CO2 or the gas in between (here
166     c not considered):
167     IF(INDEX.NE.0) THEN
168     CALL VZERO(EA,115)
169     CALL VZERO(ER,115)
170     DO I=1,115
171     CATT=ATTTRD(I,INDEX)*CAM
172     W=0
173     W=EXP(-CATT)
174     C PRINT*,'EY(I),I,CATT,ATT',EY(I),I,CATT,ATTTRD(I,INDEX)
175     c absorbed spectrum:
176     EA(I)=EY(I)*(1-W)
177     c transmitted spectrum:
178     EY(I)=EY(I)*W
179     C PRINT*,'W,EA(I),EY(I),I,INDEX',W,EA(I),EY(I),I,INDEX
180     ENDDO
181     ENDIF
182     C finally the sensitive gas:
183     IF(INDEX.EQ.3) THEN
184     goto 998
185     print*,'index,IEVENT,gamma,spettro assorbito'
186     print*,index,IEVENT,g
187     print*,(ea(i),i=1,4)
188     print*,(ea(i),i=5,8)
189     print*,(ea(i),i=9,12)
190     print*,(ea(i),i=13,16)
191     print*,(ea(i),i=17,20)
192     print*,(ea(i),i=21,24)
193     print*,(ea(i),i=25,28)
194     print*,(ea(i),i=29,32)
195     print*,(ea(i),i=33,36)
196     print*,(ea(i),i=37,40)
197     print*,(ea(i),i=41,44)
198     print*,(ea(i),i=45,48)
199     print*,(ea(i),i=49,52)
200     print*,(ea(i),i=53,56)
201     print*,(ea(i),i=57,60)
202     print*,(ea(i),i=61,64)
203     print*,(ea(i),i=65,68)
204     print*,(ea(i),i=69,72)
205     print*,(ea(i),i=73,76)
206     print*,(ea(i),i=77,80)
207     print*,(ea(i),i=81,84)
208     print*,(ea(i),i=85,88)
209     print*,(ea(i),i=89,92)
210     print*,(ea(i),i=93,96)
211     print*,(ea(i),i=97,100)
212     print*,(ea(i),i=101,104)
213     print*,(ea(i),i=105,108)
214     print*,(ea(i),i=109,112)
215     print*,(ea(i),i=113,115)
216     998 continue
217     c considering the escape peak in Xe-CO2;
218     CALL XESCAPE(ENATT,EA,ER,115)
219     SPH=0.
220     goto 997
221     print*,'index,IEVENT,gamma,spettro con escape'
222     print*,index,IEVENT,g
223     print*,(er(i),i=1,4)
224     print*,(er(i),i=5,8)
225     print*,(er(i),i=9,12)
226     print*,(er(i),i=13,16)
227     print*,(er(i),i=17,20)
228     print*,(er(i),i=21,24)
229     print*,(er(i),i=25,28)
230     print*,(er(i),i=29,32)
231     print*,(er(i),i=33,36)
232     print*,(er(i),i=37,40)
233     print*,(er(i),i=41,44)
234     print*,(er(i),i=45,48)
235     print*,(er(i),i=49,52)
236     print*,(er(i),i=53,56)
237     print*,(er(i),i=57,60)
238     print*,(er(i),i=61,64)
239     print*,(er(i),i=65,68)
240     print*,(er(i),i=69,72)
241     print*,(er(i),i=73,76)
242     print*,(er(i),i=77,80)
243     print*,(er(i),i=81,84)
244     print*,(er(i),i=85,88)
245     print*,(er(i),i=89,92)
246     print*,(er(i),i=93,96)
247     print*,(er(i),i=97,100)
248     print*,(er(i),i=101,104)
249     print*,(er(i),i=105,108)
250     print*,(er(i),i=109,112)
251     print*,(er(i),i=113,115)
252     997 continue
253     c yes escape peak:
254     ccc SPH=XTRINTEG(ENATT,ER,EINT,115)
255     SPH=XTRINTEG(ENATT,ER,EINT,75)
256     c if you don't consider the escape-peak, don't comment the next row:
257     C SPH=XTRINTEG(ENATT,EA,EINT,115)
258     C 28/9/2001: FINE TUNING OF TR:
259     c for PS ALFA=0.65 (momentum.lt.40. GeV/c)
260     c per SPS ALFA=0.69 (momentum.ge.40. GeV/c):
261     IF(ALFATR.NE.-9999.) THEN
262     SPH=ALFATR*SPH
263     ELSE
264     TROK=.FALSE.
265     WRITE(CHMAIL,10100) ALFATR
266     CALL GMAIL(1,0)
267     RETURN
268     ENDIF
269     c end 28/9/2001.
270     NPHTR=NPOISS(SPH)
271     c print*,'lay=',lay,'sph,nph=',sph,nph
272     c PRINT*,'Xe-CO2: XTRINTEG,NPOISS:',SPH,NPHTR
273     IF(NPHTR.GT.0) THEN
274     DO I=1,NPHTR
275     ccc 10 E=XTRINTER(RNDM(1)*SPH,EINT,ENATT,115)
276     10 E=XTRINTER(RNDM(1)*SPH,EINT,ENATT,75)
277     C 28/9/2001: TENTATIVO DI FINE TUNING DELLA TR:
278     ******** NEI DATI REALI NON VEDO FOTONI CON ENERGIA MAGGIORE DI 60 keV:
279     c fine modifica 28/9/2001
280     IF(E.GT.45.) THEN
281     PRINT*,'Extracted energy'
282     PRINT*,E
283     GOTO 10
284     ENDIF
285     ENPHTR=ENPHTR+E
286     ENDDO
287     c PRINT*,'Energy (keV) and photons absorbed, for event:'
288     c + ,IEVENT,ENPHTR,NPHTR ,'layer=',lay
289     C NTRHIT=NPHTR
290     C ENEHIT=ENPHTR*1.E-6
291     C* ML: SOTTRAE LA ENERGIA PERSA NEL TRD.
292     GEKINT=GEKIN-ENPHTR*1.E-6
293     GEKIN=GEKINT
294     GETOT=GEKIN +AMASS
295     VECT(7)= SQRT((GETOT+AMASS)*GEKIN)
296     C Routine to find bin number in kinetic energy table stored in ELOW(NEKBIN)
297     CALL GEKBIN
298     C* END ML.
299     ELSE
300     c PRINT*,'no photons converted in the straw'
301     ENDIF
302     IF (LAY.GT.0.AND.LAY.LE.18) THEN
303     ENTRTOT = ENTRTOT + ENPHTR
304     ENLAY(LAY) = ENLAY(LAY) + ENPHTR
305     NPHTOTR = NPHTOTR + NPHTR
306     NPHLAY(LAY)= NPHLAY(LAY) + NPHTR
307     ILI=NUMBV(NVNAME-1)
308     IHI=NUMBV(NVNAME)
309     ENTRSTRAW(ILI,IHI) = ENTRSTRAW(ILI,IHI)+ ENPHTR
310     NTRSTRAW(ILI,IHI) = NTRSTRAW(ILI,IHI)+ NPHTR
311     c PRINT*,'NPHTOTR,LAY,ENPHTR,ENTRTOT',NPHTOTR,LAY,ENPHTR,ENTRTOT
312     C PRINT*,'NTRSTRAW',NTRSTRAW(ILI,IHI),ILI,IHI
313     C PRINT*,'ENTRSTRAW,ENPHTR',ENTRSTRAW(ILI,IHI),ENPHTR
314     ELSE
315     WRITE(CHMAIL,10200)LAY
316     CALL GMAIL(1,0)
317     C PRINT*,' ERROR IN LAYER CALCULATION',LAY
318     ENDIF
319     ENDIF
320     10000 FORMAT('GPXTR error: negative mass =',F10.3)
321     10100 FORMAT('GPXTR error: ALFATR not set, TR process ',
322     + 'and his tuning will be ignored, ALFATR =',F10.3)
323     10200 FORMAT('GPXTR error in layer calculation =',F10.3)
324     RETURN
325     END

  ViewVC Help
Powered by ViewVC 1.1.23