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

Annotation of /gpamela/gpspe/gpspev.F

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3.8 - (hide annotations) (download)
Tue May 2 12:02:43 2006 UTC (18 years, 7 months ago) by bottai
Branch: MAIN
CVS Tags: v4r6
Changes since 3.7: +17 -10 lines
micrometric adjustment of spe geometry

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

  ViewVC Help
Powered by ViewVC 1.1.23