/[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.3 by cafagna, Mon Jul 25 11:53:21 2005 UTC revision 3.8 by bottai, Tue May 2 12:02:43 2006 UTC
# Line 1  Line 1 
1    
2  *  *
3  * $Id: gpspev.F,v 3.2 2005/06/21 02:42:27 cafagna Exp $  * $Id: gpspev.F,v 3.7 2005/12/16 10:20:23 cafagna Exp $
4  *  *
5  * $Log: gpspev.F,v $  * $Log: gpspev.F,v $
6  * Revision 3.2  2005/06/21 02:42:27  cafagna  * Revision 3.7  2005/12/16 10:20:23  cafagna
7  * Major modification to the geometry and to the random number chain  * Bug fixed in the new update
 *  
 * Revision 3.1.1.1  2002/07/11 16:02:14  cafagna  
 * First GPAMELA release on CVS  
 *  
 *  
 *CMZ :  2.01/00 05/04/2000  14.35.18  by  Marialuigia Ambriola  
 *CMZ :  2.00/00 03/03/2000  15.39.06  by  Francesco Cafagna  
 *CMZ :  1.02/00 07/03/97  14.48.41  by  Francesco Cafagna  
 *CMZ :  1.00/02 06/02/96  17.34.50  by  Francesco Cafagna  
 *-- Author :    Francesco Cafagna   09/12/95  
       SUBROUTINE GPSPEV  
 ************************************************************************  
 *                                                                      *  
 * Volumes definition for the silicon tracking system and magnet        *  
 * Called by: GPGEM                                                     *  
 * Author: Francesco Cafagna, 05/12/95 13.39.41                         *  
 *                                                                      *  
 ************************************************************************  
 #include "gpgeo.inc"  
 #include "gpmed.inc"  
 *  
       INTEGER IROT,IVOLU,N,NMED,NUM  
       REAL X,Y,Z  
 *  
 *  Define the SPEB     volume  
 *  
       NMED= MN2  
       CALL GSVOLU('SPEB','BOX ',NMED,SPEB, 3,IVOLU)  
 *  
 *  Define the MGFR     volume  
 *  
       NMED= MAL  
       CALL GSVOLU('MGFR','BOX ',NMED,MGFR, 3,IVOLU)  
 *  
 *  Define the MGPL     volume  
 *  
       NMED= MMAG  
       CALL GSVOLU('MGPL','BOX ',NMED,MGPL, 3,IVOLU)  
 *  
 *  Define the MGPI     volume  
 *  
       NMED= MN2  
       CALL GSVOLU('MGPI','BOX ',NMED,MGPI, 3,IVOLU)  
 *  
 *  Define the TRPB     volume  
 *  
       NMED= MAL  
       CALL GSVOLU('TRPB','BOX ',NMED,TRPB, 3,IVOLU)  
 *****  
 cC ml 20/04/05:  
 *  
 cc*  Define the TRPL     volume  
 *  Define the TPAS and TPAI volume  
 *  
       NMED= MN2  
 CC      CALL GSVOLU('TRPL','BOX ',NMED,TRPL, 3,IVOLU)  
       CALL GSVOLU('TPAS','BOX ',NMED,TPAS, 3,IVOLU)  
       NMED= MAL  
       CALL GSVOLU('TPAI','BOX ',NMED,TPAI, 3,IVOLU)  
 CC end ml.  
 ****************  
 *  
 *  Define the TRSL     volume  
 *  
 c ml: 26/11/04:  
 c      NMED= MN2  
       NMED=MSIT  
       CALL GSVOLU('TRSL','BOX ',NMED,TRSL, 3,IVOLU)  
 *  
 * Define the THBP volume  
 *  
       NMED=MG10C  
       CALL GSVOLU('THBP','BOX ',NMED,THBP, 3,IVOLU)  
 C end ml.  
8  *  *
9  *  Define the TSPA     volume  * Revision 3.6  2005/12/16 09:13:59  cafagna
10  *  * New small valume added to the tracker frame
11        NMED= MSIT  *
12        CALL GSVOLU('TSPA','BOX ',NMED,TSPA, 3,IVOLU)  * Revision 3.5  2005/12/13 10:31:29  pam-ba
13  *  * added a new volume, TPGI, in the spectrometer
14  *  Define the TRCP     volume  *
15  *  * Revision 3.4  2005/12/05 12:15:21  pam-ba
16        NMED= MCF  * new spectrometer geometry and internal magnetic field
17        CALL GSVOLU('TRCP','BOX ',NMED,TRCP, 3,IVOLU)  *
18  *  * Revision 3.3  2005/07/25 11:53:21  cafagna
19  * Positioning volume TSPA     into the mother TRSL  * Several updates. See history for details
20  *  *
21        N= 1  * Revision 3.2  2005/06/21 02:42:27  cafagna
22        X= 0.  * Major modification to the geometry and to the random number chain
23  c ml: 26/11/66:  *
24  c      Y= TRSL(2) - TSPA(2)  * Revision 3.1.1.1  2002/07/11 16:02:14  cafagna
25  C #       Y=+TRSL(2)/2  * First GPAMELA release on CVS
26        Y= 0.  *
27        Z= 0.  *
28        CALL GSPOS('TSPA',N,'TRSL',X,Y,Z,0,'ONLY')  *CMZ :  2.01/00 05/04/2000  14.35.18  by  Marialuigia Ambriola
29  C #       N= 2  *CMZ :  2.00/00 03/03/2000  15.39.06  by  Francesco Cafagna
30  C # C      Y= Y - 2.*TSPA(2)  *CMZ :  1.02/00 07/03/97  14.48.41  by  Francesco Cafagna
31  C #       Y=-TRSL(2)/2  *CMZ :  1.00/02 06/02/96  17.34.50  by  Francesco Cafagna
32  C #       CALL GSPOS('TSPA',N,'TRSL',X,Y,Z,0,'ONLY')  *-- Author :    Francesco Cafagna   09/12/95
33  c ml: 26/11/04:        SUBROUTINE GPSPEV
34  *  ************************************************************************
35  c* Positioning volume TRCP     into the mother TRSL  *                                                                      *
36  CC ml 20/04/05:  * Volumes definition for the silicon tracking system and magnet        *
37  CC* Positioning volume TRCP into mother TRPL  * Called by: GPGEM                                                     *
38  * Positioning volume TRCP into mother TRPB  * Author: Francesco Cafagna, 05/12/95 13.39.41                         *
39  *  *                                                                      *
40  c      N= 1  ************************************************************************
41  CC ml 20/04/05:  #include "gpgeo.inc"
42  cc      Z= 0.  #include "gpmed.inc"
43  cc      Y= 0.  *
44  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one        INTEGER IROT,IVOLU,N,NMED,NUM
45  C #       Z=-TRPB(3)+0.11+TRCP(3)        REAL X,Y,Z
46  C #       Y=-TRPB(2)+1.5-0.225+TRCP(2)  *
47  CC end ml.  *  Define the SPEB     volume
48        Z=-0.005  *
49        y=-0.225-TPAS(2)+TRCP(2)        NMED= MN2
50  C # end CAF mod        CALL GSVOLU('SPEB','BOX ',NMED,SPEB, 3,IVOLU)
51        DO I=1,4  *
52  CC ml 20/04/05:          *  Define the MGFR     volume
53  CC         X=-TRPL(1)+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)  *
54  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one        NMED= MAL
55  C #          X=-TRPB(1)+2.29+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)        CALL GSVOLU('MGFR','BOX ',NMED,MGFR, 3,IVOLU)
56           X=-TPAS(1)+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)  *
57  CC end ml  *  Define the MGPL     volume
58  c         CALL GSPOS('TRCP',I,'TRPL',X,Y,Z,0,'ONLY')  *
59  C #          CALL GSPOS('TRCP',I,'TRPB',X,Y,Z,0,'ONLY')        NMED= MMAG
60           CALL GSPOS('TRCP',I,'TPAS',X,Y,Z,0,'ONLY')        CALL GSVOLU('MGPL','BOX ',NMED,MGPL, 3,IVOLU)
61  C # end CAF mod  *
62        ENDDO    *  Define the MGPI     volume
63  c      X= -TRSL(1) + TRCP(1)  *
64  c      CALL GSPOS('TRCP',N,'TRSL',X,Y,Z,0,'ONLY')        NMED= MN2
65  C      N= 2        CALL GSVOLU('MGPI','BOX ',NMED,MGPI, 3,IVOLU)
66  C      X= -X  *
67  C      CALL GSPOS('TRCP',N,'TRSL',X,Y,Z,0,'ONLY')  *  Define the TRPB     volume
68  *****  *
69  cc ml 20/04/05:        NMED= MAL
70  *        CALL GSVOLU('TRPB','BOX ',NMED,TRPB, 3,IVOLU)
71  *** Positioning volume TRSL     into the mother TRPL  *****
72  * Positioning volume TRSL     into the mother TRPB  cC ml 20/04/05:
73  *  *
74  c ml: 26/11/04:  cc*  Define the TRPL     volume
75  C      Y= 0.  *  Define the TPAS and TPAI volume
76  cc      Y=THBP(2)  *
77  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one        NMED= MN2
78  C #       Y=-TRPB(2)+1.5+2*THBP(2)+TRSL(2)  CC      CALL GSVOLU('TRPL','BOX ',NMED,TRPL, 3,IVOLU)
79  C      Y=2.75        CALL GSVOLU('TPAS','BOX ',NMED,TPAS, 3,IVOLU)
80  CC      Z= 0.        NMED= MAL
81  C #       Z=-TRPB(3)+0.11+TRCP(3)        CALL GSVOLU('TPAI','BOX ',NMED,TPAI, 3,IVOLU)
82        Z=-0.005  CC end ml.
83        DO I=1, NTRSL  ****************
84           X=-TPAS(1)+2*(MOD(I-1,3)+1)*TRCP(1)+  *
85       +        (2*(MOD(I-1,3)+1)-1)*TRSL(1)  *  Define the TRSL     volume
86           IF(I.LE.3) THEN  *
87              Y=TPAS(2)-TRSL(2)  c ml: 26/11/04:
88           ELSE  c      NMED= MN2
89              Y=TPAS(2)-3*TRSL(2)        NMED=MSIT
90           ENDIF        CALL GSVOLU('TRSL','BOX ',NMED,TRSL, 3,IVOLU)
91           CALL GSPOS('TRSL',I,'TPAS',X,Y,Z,0,'ONLY')  *
92        ENDDO  * Define the THBP volume
93  C # end CAF mod  *
94  **********        NMED=MG10C
95  cc ml: 20/04/05        CALL GSVOLU('THBP','BOX ',NMED,THBP, 3,IVOLU)
96  *  C end ml.
97  ********* Positioning volume THBP     into the mother TRPL  *
98  * Positioning volume THBP     into the mother TRPB  *  Define the TSPA     volume
99  *  *
100  cc      Y=-TRSL(2)        NMED= MSIT
101  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one        CALL GSVOLU('TSPA','BOX ',NMED,TSPA, 3,IVOLU)
102  C #       Y=-TRPB(2)+1.5+THBP(2)  *
103  C # cc      Z= 0.  *  Define the TRCP     volume
104  C #       Z=-TRPB(3)+0.11+TRCP(3)  *
105        Y=-TPAS(2)+THBP(2)        NMED= MCF
106        Z=-0.005        CALL GSVOLU('TRCP','BOX ',NMED,TRCP, 3,IVOLU)
107        DO I=1, NTHBP  *
108  CC         X= -TRPL(1) + 2*I*TRCP(1)+(2*I-1)*THBP(1)  *  Define the TBAL     volume
109  C #          X=-TRPB(1)+2.29+2*I*TRCP(1)+(2*I-1)*THBP(1)  *
110           X=-TPAS(1)+2*I*TRCP(1)+(2*I-1)*THBP(1)        NMED= MAL
111  cc         CALL GSPOS('THBP',I,'TRPL',X,Y,Z,0,'ONLY')        CALL GSVOLU('TBAL','BOX ',NMED,TBAL, 3,IVOLU)
112  C #          CALL GSPOS('THBP',I,'TRPB',X,Y,Z,0,'ONLY')  *
113           CALL GSPOS('THBP',I,'TPAS',X,Y,Z,0,'ONLY')  *  Define the MGPA     volume
114        ENDDO  *
115  c end ml.        NMED= MAL
116  cc ml: 20/04/05        CALL GSVOLU('MGPA','BOX ',NMED,MGPA, 3,IVOLU)
117  *  *
118  * Positioning volume TPAI into the mother TRPB  *  Define the TPGA     volume
119  *  *
120  C # Mod By Caf on 19th Jul 2005 all volumes inside the TPAS        NMED= MN2
121        X=0        CALL GSVOLU('TPGA','BOX ',NMED,TPGA, 3,IVOLU)
122        Y=-TPAS(2)+TPAI(2)  *
123        Z=-TPAS(3)+TPAI(3)  *  Define the TPGI     volume
124  C #       X=-TRPB(1)+2.29+TPAI(1)  *
125  C #       Y=-TRPB(2)+1.5+2.5+TPAI(2)        NMED= MN2
126  C #       Z=-TRPB(3)+TPAI(3)        CALL GSVOLU('TPGI','BOX ',NMED,TPGI, 3,IVOLU)
127        CALL GSPOS('TPAI',I,'TPAS',X,Y,Z,0,'ONLY')  *
128  C # end CAF mod  *  Define the TPGU     volume
129  *  *
130  * Positioning volume TPAS into the mother TRPB        NMED= MN2
131  *        CALL GSVOLU('TPGU','BOX ',NMED,TPGU, 3,IVOLU)
132  C # Mod By Caf on 15th Jul 2005  *
133        X=0  *  Define the TPGD     volume
134        Y=-TRPB(2)+1.5+TPAS(2)  *
135        Z=0        NMED= MN2
136  C #       X=-TRPB(1)+2.29+TPAS(1)        CALL GSVOLU('TPGD','BOX ',NMED,TPGD, 3,IVOLU)
137  C #       Y=-TRPB(2)+1.5+TPAS(2)  
138  C #       Z=-TRPB(3)+0.11+2*TRCP(3)+TPAS(3)  *
139        CALL GSPOS('TPAS',I,'TRPB',X,Y,Z,0,'ONLY')  * Positioning volume TSPA     into the mother TRSL
140  c end ml.  *
141          GLUEX=XGLUE-0.0005
142          GLUEY=XGLUE
143          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          y=-TPAS(2)+TRCP(2)
161    C # end CAF mod
162          TPASSPACE=TPAS(1)-(3*TRSL(1)+4*TRCP(1)+3*GLUEX)
163          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             X=-TPAS(1)+TPASSPACE+2*(I-1)*GLUEX+(2*I-1)*TRCP(1)+
176         +      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    
195  *  
196  * Positioning volume MGPI     into the mother MGPL           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        N= 1           IF(I.LE.3) THEN
199        X= 0.  C ml: 22/9/05:
200        Y= 0.  c            Y=TPAS(2)-TRSL(2)
201        Z= 0.              Y=TPAS(2)-0.1485+0.0005-TRSL(2)
202        CALL GSPOS('MGPI',N,'MGPL',X,Y,Z,0,'ONLY')           ELSE
203  *  C            Y=TPAS(2)-3*TRSL(2)
204  * Positioning volume MGPL     into the mother MGFR              Y=TPAS(2)-0.1485-GLUEY-3*TRSL(2)
205  *           ENDIF
206        CALL GSPOS('MGPL',N,'MGFR',X,Y,Z,0,'ONLY')           CALL GSPOS('TRSL',I,'TPAS',X,Y,Z,0,'ONLY')
207  C Ml: 20/04/05:        ENDDO
208  c*  C # end CAF mod
209  c* Positioning volume TRPL     into the mother TRPB  **********
210  c*  cc ml: 20/04/05
211  c      N= 1  * Positioning volume THBP     into the mother TPAS
212  c      Z= 0.  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one
213  c      CALL GSPOS('TRPL',N,'TRPB',X,Y,Z,0,'ONLY')  C #       Y=-TRPB(2)+1.5+THBP(2)
214  c end ml.  C # cc      Z= 0.
215  *  C #       Z=-TRPB(3)+0.11+TRCP(3)
216  * Positioning volumes TRPB & MGPL into the mother SPEB  c ml: 22/9/05:
217  *  c      Y=-TPAS(2)+THBP(2)
218        N= 1        Y=-TPAS(2)+0.1485+THBP(2)
219        X= 0.  C      Z=-0.005
220        Y= SPEB(2) - TRPB(2)  c      Z=-TRPB(3)+2*TPAI(3)+TRCP(3)
221        Z= SPEB(3) - TRPB(3)        Z=TRPB(3)-2*TPAI(3)-TRCP(3)
222        CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY')        DO I=1, NTHBP
223        DO I=1, 5  CC         X= -TRPL(1) + 2*I*TRCP(1)+(2*I-1)*THBP(1)
224           X= 0.  C #          X=-TRPB(1)+2.29+2*I*TRCP(1)+(2*I-1)*THBP(1)
225           Y= 0.  c ml: 21/9/05 introducing the glue between the carbon barrel and the silicon
226           Z= Z - TRPB(3) - MGFR(3)  c       ladders
227           N= I  c         X=-TPAS(1)+2*I*TRCP(1)+(2*I-1)*THBP(1)
228           CALL GSPOS('MGFR',N,'SPEB',X,Y,Z,0,'ONLY')           X=-TPAS(1)+TPASSPACE+2*I*TRCP(1)+(2*I-1)*THBP(1)+
229           Y= SPEB(2) - TRPB(2)       +      (2*(MOD(I-1,3)+1)-1)*GLUEX
230           Z= Z - MGFR(3) - TRPB(3)           CALL GSPOS('THBP',I,'TPAS',X,Y,Z,0,'ONLY')
231           N= (I+1)        ENDDO
232           IF(I.EQ.5) THEN  c end ml.
233              CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY')  cc ml: 20/04/05
234           ELSE  *
235              CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY')  * Positioning volume TPAI into the mother TPAS
236           ENDIF  *
237        ENDDO  C # Mod By Caf on 19th Jul 2005 all volumes inside the TPAS
238  *        X=0
239        RETURN        Y=-TPAS(2)+TPAI(2)
240        END  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

Legend:
Removed from v.3.3  
changed lines
  Added in v.3.8

  ViewVC Help
Powered by ViewVC 1.1.23