/[PAMELA software]/gpamela/gpspe/gpspev.F
ViewVC logotype

Annotation of /gpamela/gpspe/gpspev.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.10 - (hide annotations) (download)
Fri Dec 1 12:25:51 2006 UTC (18 years ago) by cafagna
Branch: MAIN
CVS Tags: v4r9, v4r14, v4r12, v4r13, v4r10, v4r11
Changes since 3.9: +392 -390 lines
 New Antiproton annihilation cross section added

1 cafagna 3.10 *
2     * $Id: gpspev.F,v 3.9 2006/06/30 15:38:16 pam-ba Exp $
3     *
4     * $Log: gpspev.F,v $
5     * Revision 3.9 2006/06/30 15:38:16 pam-ba
6     * S22 and S12 heights positioned in GPAMELA at the nominal heights in PAMELA (see document: Main geometrical parameters of the PAMELA sub-detectors, 20 December 2005)
7     *
8     * Revision 3.8 2006/05/02 12:02:43 bottai
9     * micrometric adjustment of spe geometry
10     *
11     * Revision 3.7 2005/12/16 10:20:23 cafagna
12     * Bug fixed in the new update
13     *
14     * Revision 3.6 2005/12/16 09:13:59 cafagna
15     * New small valume added to the tracker frame
16     *
17     * Revision 3.5 2005/12/13 10:31:29 pam-ba
18     * added a new volume, TPGI, in the spectrometer
19     *
20     * Revision 3.4 2005/12/05 12:15:21 pam-ba
21     * new spectrometer geometry and internal magnetic field
22     *
23     * Revision 3.3 2005/07/25 11:53:21 cafagna
24     * Several updates. See history for details
25     *
26     * Revision 3.2 2005/06/21 02:42:27 cafagna
27     * Major modification to the geometry and to the random number chain
28     *
29     * Revision 3.1.1.1 2002/07/11 16:02:14 cafagna
30     * First GPAMELA release on CVS
31     *
32     *
33     *CMZ : 2.01/00 05/04/2000 14.35.18 by Marialuigia Ambriola
34     *CMZ : 2.00/00 03/03/2000 15.39.06 by Francesco Cafagna
35     *CMZ : 1.02/00 07/03/97 14.48.41 by Francesco Cafagna
36     *CMZ : 1.00/02 06/02/96 17.34.50 by Francesco Cafagna
37     *-- Author : Francesco Cafagna 09/12/95
38     SUBROUTINE GPSPEV
39     ************************************************************************
40     * *
41     * Volumes definition for the silicon tracking system and magnet *
42     * Called by: GPGEM *
43     * Author: Francesco Cafagna, 05/12/95 13.39.41 *
44     * *
45     ************************************************************************
46     #include "gpgeo.inc"
47     #include "gpmed.inc"
48     *
49     INTEGER IROT,IVOLU,N,NMED,NUM
50     REAL X,Y,Z
51     *
52     * Define the SPEB volume
53     *
54     NMED= MN2
55     CALL GSVOLU('SPEB','BOX ',NMED,SPEB, 3,IVOLU)
56     *
57     * Define the MGFR volume
58     *
59     NMED= MAL
60     CALL GSVOLU('MGFR','BOX ',NMED,MGFR, 3,IVOLU)
61     *
62     * Define the MGPL volume
63     *
64     NMED= MMAG
65     CALL GSVOLU('MGPL','BOX ',NMED,MGPL, 3,IVOLU)
66     *
67     * Define the MGPI volume
68     *
69     NMED= MN2
70     CALL GSVOLU('MGPI','BOX ',NMED,MGPI, 3,IVOLU)
71     *
72     * Define the TRPB volume
73     *
74     NMED= MAL
75     CALL GSVOLU('TRPB','BOX ',NMED,TRPB, 3,IVOLU)
76     *****
77     cC ml 20/04/05:
78     *
79     cc* Define the TRPL volume
80     * Define the TPAS and TPAI volume
81     *
82     NMED= MN2
83     CC CALL GSVOLU('TRPL','BOX ',NMED,TRPL, 3,IVOLU)
84     CALL GSVOLU('TPAS','BOX ',NMED,TPAS, 3,IVOLU)
85     NMED= MAL
86     CALL GSVOLU('TPAI','BOX ',NMED,TPAI, 3,IVOLU)
87     CC end ml.
88     ****************
89     *
90     * Define the TRSL volume
91     *
92     c ml: 26/11/04:
93     c NMED= MN2
94     NMED=MSIT
95     CALL GSVOLU('TRSL','BOX ',NMED,TRSL, 3,IVOLU)
96     *
97     * Define the THBP volume
98     *
99     NMED=MG10C
100     CALL GSVOLU('THBP','BOX ',NMED,THBP, 3,IVOLU)
101     C end ml.
102     *
103     * Define the TSPA volume
104     *
105     NMED= MSIT
106     CALL GSVOLU('TSPA','BOX ',NMED,TSPA, 3,IVOLU)
107     *
108     * Define the TRCP volume
109     *
110     NMED= MCF
111     CALL GSVOLU('TRCP','BOX ',NMED,TRCP, 3,IVOLU)
112     *
113     * Define the TBAL volume
114     *
115     NMED= MAL
116     CALL GSVOLU('TBAL','BOX ',NMED,TBAL, 3,IVOLU)
117     *
118     * Define the MGPA volume
119     *
120     NMED= MAL
121     CALL GSVOLU('MGPA','BOX ',NMED,MGPA, 3,IVOLU)
122     *
123     * Define the TPGA volume
124     *
125     NMED= MN2
126     CALL GSVOLU('TPGA','BOX ',NMED,TPGA, 3,IVOLU)
127     *
128     * Define the TPGI volume
129     *
130     NMED= MN2
131     CALL GSVOLU('TPGI','BOX ',NMED,TPGI, 3,IVOLU)
132     *
133     * Define the TPGU volume
134     *
135     NMED= MN2
136     CALL GSVOLU('TPGU','BOX ',NMED,TPGU, 3,IVOLU)
137     *
138     * Define the TPGD volume
139     *
140     NMED= MN2
141     CALL GSVOLU('TPGD','BOX ',NMED,TPGD, 3,IVOLU)
142    
143     *
144     * Positioning volume TSPA into the mother TRSL
145     *
146     GLUEX=XGLUE-0.0005
147     GLUEY=XGLUE
148     N= 1
149     X= 0.
150     Y= 0.
151     Z= 0.
152     CALL GSPOS('TSPA',N,'TRSL',X,Y,Z,0,'ONLY')
153     C # N= 2
154     C # C Y= Y - 2.*TSPA(2)
155     C # Y=-TRSL(2)/2
156     C # CALL GSPOS('TSPA',N,'TRSL',X,Y,Z,0,'ONLY')
157     c ml: 26/11/04:
158     * Positioning volume TRCP into mother TPAS
159     C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one
160     C # Z=-TRPB(3)+0.11+TRCP(3)
161     C # Y=-TRPB(2)+1.5-0.225+TRCP(2)
162     CC end ml.
163     c Z=-TRPB(3)+2*TPAI(3)+TRCP(3)
164     Z=TRPB(3)-2*TPAI(3)-TRCP(3)
165     y=-TPAS(2)+TRCP(2)
166     C # end CAF mod
167     TPASSPACE=TPAS(1)-(3*TRSL(1)+4*TRCP(1)+3*GLUEX)
168     DO I=1,4
169     CC ml 20/04/05:
170     CC X=-TRPL(1)+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)
171     C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one
172     C # X=-TRPB(1)+2.29+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)
173     c ml: 19/9/05: introducing the glue between TRCP and the silicon ladders.
174     c for now the glue is a space of nitrogen of 0.015 mm
175     c X=-TPAS(1)+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)
176     C Ml. 15/12/05: introducing a space (along x) between the inner part of the
177     c aluminum frame and respectively the first and the last carbon fiber barrel.
178     c It is has been done increasing the dimension of TPAS along x:
179     C X=-TPAS(1)+2*(I-1)*XGLUE+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)
180     X=-TPAS(1)+TPASSPACE+2*(I-1)*GLUEX+(2*I-1)*TRCP(1)+
181     + 2*(I-1)*TRSL(1)
182     CC end ml
183     CALL GSPOS('TRCP',I,'TPAS',X,Y,Z,0,'ONLY')
184     C # end CAF mod
185     ENDDO
186     cc ml 20/04/05:
187     * Positioning volume TRSL into the mother TPAS
188     C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one
189     C # Y=-TRPB(2)+1.5+2*THBP(2)+TRSL(2)
190     C Y=2.75
191     CC Z= 0.
192     C Z=-0.005
193     c Z=-TRPB(3)+2*TPAI(3)+TRCP(3)
194     Z=TRPB(3)-2*TPAI(3)-TRCP(3)
195     DO I=1, NTRSL
196     c ml: 20/9/05 introducing the glue between TRCP and the silicon ladders.
197     c X=-TPAS(1)+2*(MOD(I-1,3)+1)*TRCP(1)+
198     c + (2*(MOD(I-1,3)+1)-1)*TRSL(1)
199     X=-TPAS(1)+TPASSPACE+2*(MOD(I-1,3)+1)*TRCP(1)+
200     + (2*(MOD(I-1,3)+1)-1)*GLUEX+(2*(MOD(I-1,3)+1)-1)*TRSL(1)
201     IF(I.LE.3) THEN
202     C ml: 22/9/05:
203     c Y=TPAS(2)-TRSL(2)
204     Y=TPAS(2)-0.1485+0.0005-TRSL(2)
205     ELSE
206     C Y=TPAS(2)-3*TRSL(2)
207     Y=TPAS(2)-0.1485-GLUEY-3*TRSL(2)
208     ENDIF
209     CALL GSPOS('TRSL',I,'TPAS',X,Y,Z,0,'ONLY')
210     ENDDO
211     C # end CAF mod
212     **********
213     cc ml: 20/04/05
214     * Positioning volume THBP into the mother TPAS
215     C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one
216     C # Y=-TRPB(2)+1.5+THBP(2)
217     C # cc Z= 0.
218     C # Z=-TRPB(3)+0.11+TRCP(3)
219     c ml: 22/9/05:
220     c Y=-TPAS(2)+THBP(2)
221     Y=-TPAS(2)+0.1485+THBP(2)
222     C Z=-0.005
223     c Z=-TRPB(3)+2*TPAI(3)+TRCP(3)
224     Z=TRPB(3)-2*TPAI(3)-TRCP(3)
225     DO I=1, NTHBP
226     CC X= -TRPL(1) + 2*I*TRCP(1)+(2*I-1)*THBP(1)
227     C # X=-TRPB(1)+2.29+2*I*TRCP(1)+(2*I-1)*THBP(1)
228     c ml: 21/9/05 introducing the glue between the carbon barrel and the silicon
229     c ladders
230     c X=-TPAS(1)+2*I*TRCP(1)+(2*I-1)*THBP(1)
231     X=-TPAS(1)+TPASSPACE+2*I*TRCP(1)+(2*I-1)*THBP(1)+
232     + (2*(MOD(I-1,3)+1)-1)*GLUEX
233     CALL GSPOS('THBP',I,'TPAS',X,Y,Z,0,'ONLY')
234     ENDDO
235     c end ml.
236     cc ml: 20/04/05
237     *
238     * Positioning volume TPAI into the mother TPAS
239     *
240     C # Mod By Caf on 19th Jul 2005 all volumes inside the TPAS
241     X=0
242     Y=-TPAS(2)+TPAI(2)
243     c Z=-TPAS(3)+TPAI(3)
244     Z=TRPB(3)-TPAI(3)
245     C # X=-TRPB(1)+2.29+TPAI(1)
246     C # Y=-TRPB(2)+1.5+2.5+TPAI(2)
247     C # Z=-TRPB(3)+TPAI(3)
248     CALL GSPOS('TPAI',I,'TPAS',X,Y,Z,0,'ONLY')
249     C # end CAF mod
250     *
251     * Positioning volume TPAS into the mother TRPB
252     *
253     C # Mod By Caf on 15th Jul 2005
254     X=0
255     Y=-TRPB(2)+1.5+TPAS(2)
256     Z=0
257     C # X=-TRPB(1)+2.29+TPAS(1)
258     C # Y=-TRPB(2)+1.5+TPAS(2)
259     C # Z=-TRPB(3)+0.11+2*TRCP(3)+TPAS(3)
260     CALL GSPOS('TPAS',I,'TRPB',X,Y,Z,0,'ONLY')
261     c end ml.
262     *
263     * Positioning volume MGPA into the mother MGPL
264     *
265     N= 1
266     X= 0.
267     Y= 0.
268     Z= 0.
269     CALL GSPOS('MGPA',N,'MGPL',X,Y,Z,0,'ONLY')
270     *
271     * Positioning volume TPGD into the mother MGFR
272     *
273     X=0.
274     Z=-MGFR(3)+TPGD(3)
275     Y=0.
276     CALL GSPOS('TPGD',N,'MGFR',X,Y,Z,0,'ONLY')
277     *
278     * Positioning volume TPGI into the mother MGFR under MGPL
279     *
280     N=1
281     X=0.
282     Z=-MGFR(3)+2*TPGD(3)+TPGI(3)
283     Y=0.
284     CALL GSPOS('TPGI',N,'MGFR',X,Y,Z,0,'ONLY')
285     *
286     * Positioning volume MGPI into the mother MGPL
287     *
288     N= 1
289     X= 0.
290     Y= 0.
291     CC ML 10/11/05: Positioning volume MGPI into the mother MGPA
292     Z= 0.
293     CALL GSPOS('MGPI',N,'MGPA',X,Y,Z,0,'ONLY')
294     C Z= -MGFR(3)+2*TPGD(3)+MGPI(3)
295     C CALL GSPOS('MGPI',N,'MGFR',X,Y,Z,0,'ONLY')
296     *
297     * Positioning volume MGPL into the mother MGFR
298     *
299     c ml: 10/11/05
300     N=1
301     c Z=-MGFR(3)+MGPL(3)
302     Z=-MGFR(3)+2*(TPGD(3)+TPGI(3))+MGPL(3)
303     CALL GSPOS('MGPL',N,'MGFR',X,Y,Z,0,'ONLY')
304     *
305     * Positioning volume TPGI into the mother MGFR above MGPL
306     *
307     N=2
308     X=0.
309     Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3))+TPGI(3)
310     Y=0.
311     CALL GSPOS('TPGI',N,'MGFR',X,Y,Z,0,'ONLY')
312     *
313     * Positioning volume TPGA into the mother MGFR
314     *
315     C ML: 10/11/05
316     N=1
317     X=0.
318     Y=MGFR(2)-2*(MGFR(2)-TRPB(2))-TPGA(2)
319     C Z=-MGFR(3)+2*MGPL(3)+TPGA(3)
320     C Z=MGFR(3)-2*TPGU(3)-2*TRPB(3)-TPGA(3)
321     Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3)+TPGI(3))+TPGA(3)
322     C Y=-0.75
323     CALL GSPOS('TPGA',N,'MGFR',X,Y,Z,0,'ONLY')
324     *
325     * Positioning volumes TRPB & MGPL into the mother SPEB
326     *
327     N= 1
328     X= 0.
329     C Y= SPEB(2) - TRPB(2)
330     Y= -MGFR(2) + TRPB(2)
331     C Z= SPEB(3) - TRPB(3)
332     c Z=-MGFR(3)+2*MGPL(3)+2*TPGA(3)+TRPB(3)
333     C Z=MGFR(3)-2*TPGU(3)-TRPB(3)
334     Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3)+TPGI(3)+TPGA(3))+TRPB(3)
335     C CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY')
336     CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,0,'ONLY')
337     c CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,9,'ONLY')
338     Z=SPEB(3)
339     DO I=1, 5
340     X= 0.
341     Y= 0.
342     C Z= Z - TRPB(3) - MGFR(3)
343     Z=Z-MGFR(3)
344     N= I
345     CALL GSPOS('MGFR',N,'SPEB',X,Y,Z,0,'ONLY')
346     C Y= SPEB(2) - TRPB(2)
347     C Z= Z - MGFR(3) - TRPB(3)
348     C N= (I+1)
349     C IF(I.EQ.5) THEN
350     CC CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY')
351     C CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,10,'ONLY')
352     C ELSE
353     CC CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY')
354     C CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,0,'ONLY')
355     C ENDIF
356     Z=Z-MGFR(3)
357     ENDDO
358     N=2
359     X=0.
360     Y=MGFR(2) - TRPB(2)
361     Z=Z-TRPB(3)
362     ZTRPB=Z
363     c CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,4,'ONLY')
364     CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY')
365     *
366     * Positioning volume TBAL into the mother SPEB
367     *
368     DO I=1,2
369     C DTBAL is the distance along x of the volumes TBAL from the end of TRPB
370     DTBAL=3.6
371     N=I
372     IF(I.EQ.1) THEN
373     X=TRPB(1)-3.6-TBAL(1)
374     ELSE
375     X=-(TRPB(1)-3.6-TBAL(1))
376     ENDIF
377     Y=MGFR(2) - 2*TRPB(2)-TBAL(2)
378     Z=ZTRPB
379     CALL GSPOS('TBAL',N,'SPEB',X,Y,Z,0,'ONLY')
380     ENDDO
381     *
382     * Positioning volume TPGU into the mother MGFR
383     *
384     X=0.
385     C Z=MGFR(3)-TPGU(3)
386     Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3)+TPGI(3)+TPGA(3)+TRPB(3))+
387     + TPGU(3)
388     Y=-MGFR(2)+TRPB(2)
389     CALL GSPOS('TPGU',N,'MGFR',X,Y,Z,0,'ONLY')
390     *
391     RETURN
392     END

  ViewVC Help
Powered by ViewVC 1.1.23