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

Annotation of /gpamela/gpspe/gpspev.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.7 - (hide annotations) (download)
Fri Dec 16 10:20:23 2005 UTC (18 years, 11 months ago) by cafagna
Branch: MAIN
CVS Tags: v4r4, v4r5
Changes since 3.6: +5 -30 lines
Bug fixed in the new update

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

  ViewVC Help
Powered by ViewVC 1.1.23