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

Diff of /gpamela/gpspe/gpspev.F

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

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

Legend:
Removed from v.3.2  
changed lines
  Added in v.3.9

  ViewVC Help
Powered by ViewVC 1.1.23