/[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.4 by pam-ba, Mon Dec 5 12:15: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.3 2005/07/25 11:53:21 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.3  2005/07/25 11:53:21  cafagna  * Revision 3.7  2005/12/16 10:20:23  cafagna
7  * Several updates. See history for details  * Bug fixed in the new update
 *  
 * Revision 3.2  2005/06/21 02:42:27  cafagna  
 * Major modification to the geometry and to the random number chain  
 *  
 * 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.  
 *  
 *  Define the TSPA     volume  
 *  
       NMED= MSIT  
       CALL GSVOLU('TSPA','BOX ',NMED,TSPA, 3,IVOLU)  
 *  
 *  Define the TRCP     volume  
 *  
       NMED= MCF  
       CALL GSVOLU('TRCP','BOX ',NMED,TRCP, 3,IVOLU)  
 *  
 *  Define the MGPA     volume  
8  *  *
9        NMED= MAL  * Revision 3.6  2005/12/16 09:13:59  cafagna
10        CALL GSVOLU('MGPA','BOX ',NMED,MGPA, 3,IVOLU)  * New small valume added to the tracker frame
11  *  *
12  *  Define the TPGA     volume  * Revision 3.5  2005/12/13 10:31:29  pam-ba
13  *  * added a new volume, TPGI, in the spectrometer
14        NMED= MN2  *
15        CALL GSVOLU('TPGA','BOX ',NMED,TPGA, 3,IVOLU)  * Revision 3.4  2005/12/05 12:15:21  pam-ba
16  *  * new spectrometer geometry and internal magnetic field
17  *  Define the TPGU     volume  *
18  *  * Revision 3.3  2005/07/25 11:53:21  cafagna
19        NMED= MN2  * Several updates. See history for details
20        CALL GSVOLU('TPGU','BOX ',NMED,TPGU, 3,IVOLU)  *
21  *  * Revision 3.2  2005/06/21 02:42:27  cafagna
22  *  Define the TPGD     volume  * Major modification to the geometry and to the random number chain
23  *  *
24        NMED= MN2  * Revision 3.1.1.1  2002/07/11 16:02:14  cafagna
25        CALL GSVOLU('TPGD','BOX ',NMED,TPGD, 3,IVOLU)  * 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          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 TSPA     into the mother TRSL           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('TSPA',N,'TRSL',X,Y,Z,0,'ONLY')           ELSE
203  C #       N= 2  C            Y=TPAS(2)-3*TRSL(2)
204  C # C      Y= Y - 2.*TSPA(2)              Y=TPAS(2)-0.1485-GLUEY-3*TRSL(2)
205  C #       Y=-TRSL(2)/2           ENDIF
206  C #       CALL GSPOS('TSPA',N,'TRSL',X,Y,Z,0,'ONLY')           CALL GSPOS('TRSL',I,'TPAS',X,Y,Z,0,'ONLY')
207  c ml: 26/11/04:        ENDDO
208  * Positioning volume TRCP into mother TPAS  C # end CAF mod
209  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one  **********
210  C #       Z=-TRPB(3)+0.11+TRCP(3)  cc ml: 20/04/05
211  C #       Y=-TRPB(2)+1.5-0.225+TRCP(2)  * Positioning volume THBP     into the mother TPAS
212  CC end ml.  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one
213  c      Z=-TRPB(3)+2*TPAI(3)+TRCP(3)  C #       Y=-TRPB(2)+1.5+THBP(2)
214        Z=TRPB(3)-2*TPAI(3)-TRCP(3)  C # cc      Z= 0.
215        y=-0.225-TPAS(2)+TRCP(2)  C #       Z=-TRPB(3)+0.11+TRCP(3)
216  C # end CAF mod  c ml: 22/9/05:
217        DO I=1,4  c      Y=-TPAS(2)+THBP(2)
218  CC ml 20/04/05:                Y=-TPAS(2)+0.1485+THBP(2)
219  CC         X=-TRPL(1)+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)  C      Z=-0.005
220  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one  c      Z=-TRPB(3)+2*TPAI(3)+TRCP(3)
221  C #          X=-TRPB(1)+2.29+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)        Z=TRPB(3)-2*TPAI(3)-TRCP(3)
222  c ml: 19/9/05: introducing the glue between TRCP and the silicon ladders.        DO I=1, NTHBP
223  c              for now the glue is a space of nitrogen of 0.015 mm  CC         X= -TRPL(1) + 2*I*TRCP(1)+(2*I-1)*THBP(1)
224  c         X=-TPAS(1)+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)  C #          X=-TRPB(1)+2.29+2*I*TRCP(1)+(2*I-1)*THBP(1)
225           X=-TPAS(1)+2*(I-1)*0.0015+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1)  c ml: 21/9/05 introducing the glue between the carbon barrel and the silicon
226  CC end ml  c       ladders
227           CALL GSPOS('TRCP',I,'TPAS',X,Y,Z,0,'ONLY')  c         X=-TPAS(1)+2*I*TRCP(1)+(2*I-1)*THBP(1)
228  C # end CAF mod           X=-TPAS(1)+TPASSPACE+2*I*TRCP(1)+(2*I-1)*THBP(1)+
229        ENDDO         +      (2*(MOD(I-1,3)+1)-1)*GLUEX
230  cc ml 20/04/05:           CALL GSPOS('THBP',I,'TPAS',X,Y,Z,0,'ONLY')
231  * Positioning volume TRSL     into the mother TPAS        ENDDO
232  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one  c end ml.
233  C #       Y=-TRPB(2)+1.5+2*THBP(2)+TRSL(2)  cc ml: 20/04/05
234  C      Y=2.75  *
235  CC      Z= 0.  * Positioning volume TPAI into the mother TPAS
236  C      Z=-0.005  *
237  c      Z=-TRPB(3)+2*TPAI(3)+TRCP(3)  C # Mod By Caf on 19th Jul 2005 all volumes inside the TPAS
238        Z=TRPB(3)-2*TPAI(3)-TRCP(3)        X=0
239        DO I=1, NTRSL        Y=-TPAS(2)+TPAI(2)
240  c ml: 20/9/05 introducing the glue between TRCP and the silicon ladders.  c      Z=-TPAS(3)+TPAI(3)
241  c         X=-TPAS(1)+2*(MOD(I-1,3)+1)*TRCP(1)+        Z=TRPB(3)-TPAI(3)
242  c     +        (2*(MOD(I-1,3)+1)-1)*TRSL(1)  C #       X=-TRPB(1)+2.29+TPAI(1)
243           X=-TPAS(1)+2*(MOD(I-1,3)+1)*TRCP(1)+  C #       Y=-TRPB(2)+1.5+2.5+TPAI(2)
244       +   (2*(MOD(I-1,3)+1)-1)*0.0015+(2*(MOD(I-1,3)+1)-1)*TRSL(1)          C #       Z=-TRPB(3)+TPAI(3)
245           IF(I.LE.3) THEN        CALL GSPOS('TPAI',I,'TPAS',X,Y,Z,0,'ONLY')
246  C ml: 22/9/05:  C # end CAF mod
247  c            Y=TPAS(2)-TRSL(2)  *
248              Y=TPAS(2)-0.1485-TRSL(2)  * Positioning volume TPAS into the mother TRPB
249           ELSE  *
250  C            Y=TPAS(2)-3*TRSL(2)  C # Mod By Caf on 15th Jul 2005
251              Y=TPAS(2)-0.1485-0.0015-3*TRSL(2)        X=0
252           ENDIF        Y=-TRPB(2)+1.5+TPAS(2)
253           CALL GSPOS('TRSL',I,'TPAS',X,Y,Z,0,'ONLY')        Z=0
254        ENDDO  C #       X=-TRPB(1)+2.29+TPAS(1)
255  C # end CAF mod  C #       Y=-TRPB(2)+1.5+TPAS(2)
256  **********  C #       Z=-TRPB(3)+0.11+2*TRCP(3)+TPAS(3)
257  cc ml: 20/04/05        CALL GSPOS('TPAS',I,'TRPB',X,Y,Z,0,'ONLY')
258  * Positioning volume THBP     into the mother TPAS  c end ml.
259  C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one  *
260  C #       Y=-TRPB(2)+1.5+THBP(2)  * Positioning volume MGPA     into the mother MGPL
261  C # cc      Z= 0.  *
262  C #       Z=-TRPB(3)+0.11+TRCP(3)        N= 1
263  c ml: 22/9/05:        X= 0.
264  c      Y=-TPAS(2)+THBP(2)        Y= 0.
265        Y=-TPAS(2)+0.1485+THBP(2)        Z= 0.
266  C      Z=-0.005        CALL GSPOS('MGPA',N,'MGPL',X,Y,Z,0,'ONLY')
267  c      Z=-TRPB(3)+2*TPAI(3)+TRCP(3)  *
268        Z=TRPB(3)-2*TPAI(3)-TRCP(3)  * Positioning volume TPGD     into the mother MGFR
269        DO I=1, NTHBP  *
270  CC         X= -TRPL(1) + 2*I*TRCP(1)+(2*I-1)*THBP(1)        X=0.
271  C #          X=-TRPB(1)+2.29+2*I*TRCP(1)+(2*I-1)*THBP(1)        Z=-MGFR(3)+TPGD(3)
272  c ml: 21/9/05 introducing the glue between the carbon barrel and the silicon        Y=0.
273  c       ladders        CALL GSPOS('TPGD',N,'MGFR',X,Y,Z,0,'ONLY')
274  c         X=-TPAS(1)+2*I*TRCP(1)+(2*I-1)*THBP(1)  *
275           X=-TPAS(1)+2*I*TRCP(1)+(2*I-1)*THBP(1)+  * Positioning volume TPGI     into the mother MGFR under MGPL
276       +      (2*(MOD(I-1,3)+1)-1)*0.0015  *
277           CALL GSPOS('THBP',I,'TPAS',X,Y,Z,0,'ONLY')        N=1
278        ENDDO        X=0.
279  c end ml.        Z=-MGFR(3)+2*TPGD(3)+TPGI(3)
280  cc ml: 20/04/05        Y=0.
281  *        CALL GSPOS('TPGI',N,'MGFR',X,Y,Z,0,'ONLY')
282  * Positioning volume TPAI into the mother TPAS  *
283  *  * Positioning volume MGPI     into the mother MGPL
284  C # Mod By Caf on 19th Jul 2005 all volumes inside the TPAS  *
285        X=0        N= 1
286        Y=-TPAS(2)+TPAI(2)        X= 0.
287  c      Z=-TPAS(3)+TPAI(3)        Y= 0.
288        Z=TRPB(3)-TPAI(3)  CC ML 10/11/05:  Positioning volume MGPI     into the mother MGPA
289  C #       X=-TRPB(1)+2.29+TPAI(1)        Z= 0.
290  C #       Y=-TRPB(2)+1.5+2.5+TPAI(2)        CALL GSPOS('MGPI',N,'MGPA',X,Y,Z,0,'ONLY')
291  C #       Z=-TRPB(3)+TPAI(3)  C      Z= -MGFR(3)+2*TPGD(3)+MGPI(3)
292        CALL GSPOS('TPAI',I,'TPAS',X,Y,Z,0,'ONLY')  C      CALL GSPOS('MGPI',N,'MGFR',X,Y,Z,0,'ONLY')
293  C # end CAF mod  *
294  *  * Positioning volume MGPL     into the mother MGFR
295  * Positioning volume TPAS into the mother TRPB  *
296  *  c ml: 10/11/05
297  C # Mod By Caf on 15th Jul 2005        N=1
298        X=0  c      Z=-MGFR(3)+MGPL(3)
299        Y=-TRPB(2)+1.5+TPAS(2)        Z=-MGFR(3)+2*(TPGD(3)+TPGI(3))+MGPL(3)
300        Z=0        CALL GSPOS('MGPL',N,'MGFR',X,Y,Z,0,'ONLY')
301  C #       X=-TRPB(1)+2.29+TPAS(1)  *
302  C #       Y=-TRPB(2)+1.5+TPAS(2)  * Positioning volume TPGI     into the mother MGFR above MGPL
303  C #       Z=-TRPB(3)+0.11+2*TRCP(3)+TPAS(3)  *
304        CALL GSPOS('TPAS',I,'TRPB',X,Y,Z,0,'ONLY')        N=2
305  c end ml.        X=0.
306  *        Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3))+TPGI(3)
307  * Positioning volume MGPA     into the mother MGPL        Y=0.
308  *        CALL GSPOS('TPGI',N,'MGFR',X,Y,Z,0,'ONLY')
309        N= 1  *
310        X= 0.  * Positioning volume TPGA     into the mother MGFR
311        Y= 0.  *
312        Z= 0.  C ML: 10/11/05
313        CALL GSPOS('MGPA',N,'MGPL',X,Y,Z,0,'ONLY')        N=1
314  *        X=0.
315  * Positioning volume TPGD     into the mother MGFR        Y=MGFR(2)-2*(MGFR(2)-TRPB(2))-TPGA(2)
316  *  C      Z=-MGFR(3)+2*MGPL(3)+TPGA(3)
317        X=0.  C      Z=MGFR(3)-2*TPGU(3)-2*TRPB(3)-TPGA(3)
318        Z=-MGFR(3)+TPGD(3)        Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3)+TPGI(3))+TPGA(3)
319        Y=0.  C      Y=-0.75
320        CALL GSPOS('TPGD',N,'MGFR',X,Y,Z,0,'ONLY')        CALL GSPOS('TPGA',N,'MGFR',X,Y,Z,0,'ONLY')
321  *  *
322  * Positioning volume MGPI     into the mother MGPL  * Positioning volumes TRPB & MGPL into the mother SPEB
323  *  *
324        N= 1        N= 1
325        X= 0.        X= 0.
326        Y= 0.  C      Y= SPEB(2) - TRPB(2)
327  CC ML 10/11/05:  Positioning volume MGPI     into the mother MGFR        Y= -MGFR(2) + TRPB(2)
328        Z= 0.  C      Z= SPEB(3) - TRPB(3)
329        CALL GSPOS('MGPI',N,'MGPA',X,Y,Z,0,'ONLY')  c      Z=-MGFR(3)+2*MGPL(3)+2*TPGA(3)+TRPB(3)
330  C      Z= -MGFR(3)+2*TPGD(3)+MGPI(3)  C      Z=MGFR(3)-2*TPGU(3)-TRPB(3)
331  C      CALL GSPOS('MGPI',N,'MGFR',X,Y,Z,0,'ONLY')        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  * Positioning volume MGPL     into the mother MGFR        CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,0,'ONLY')
334  *  c      CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,9,'ONLY')
335  c ml: 10/11/05        Z=SPEB(3)
336  c      Z=-MGFR(3)+MGPL(3)        DO I=1, 5
337        Z=-MGFR(3)+2*TPGD(3)+MGPI(3)           X= 0.
338        CALL GSPOS('MGPL',N,'MGFR',X,Y,Z,0,'ONLY')           Y= 0.
339  *  C         Z= Z - TRPB(3) - MGFR(3)
340  * Positioning volume TPGA     into the mother MGFR           Z=Z-MGFR(3)
341  *           N= I
342  C ML: 10/11/05           CALL GSPOS('MGFR',N,'SPEB',X,Y,Z,0,'ONLY')
343        X=0.  C         Y= SPEB(2) - TRPB(2)
344        Y=MGFR(2)-2*(MGFR(2)-TRPB(2))-TPGA(2)  C         Z= Z - MGFR(3) - TRPB(3)
345  C      Z=-MGFR(3)+2*MGPL(3)+TPGA(3)  C         N= (I+1)
346        Z=MGFR(3)-2*TPGU(3)-2*TRPB(3)-TPGA(3)  C         IF(I.EQ.5) THEN
347  C      Y=-0.75  CC            CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY')
348        CALL GSPOS('TPGA',N,'MGFR',X,Y,Z,0,'ONLY')  C            CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,10,'ONLY')
349  *  C         ELSE
350  * Positioning volumes TRPB & MGPL into the mother SPEB  CC            CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY')
351  *  C            CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,0,'ONLY')
352        N= 1  C         ENDIF
353        X= 0.           Z=Z-MGFR(3)
354  C      Y= SPEB(2) - TRPB(2)        ENDDO
355        Y= -MGFR(2) + TRPB(2)        N=2
356  C      Z= SPEB(3) - TRPB(3)        X=0.
357  c      Z=-MGFR(3)+2*MGPL(3)+2*TPGA(3)+TRPB(3)        Y=MGFR(2) - TRPB(2)
358        Z=MGFR(3)-2*TPGU(3)-TRPB(3)        Z=Z-TRPB(3)
359  C      CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY')        ZTRPB=Z
360        CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,0,'ONLY')  c      CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,4,'ONLY')
361  c      CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,9,'ONLY')        CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY')
362        Z=SPEB(3)  *
363        DO I=1, 5  * Positioning volume TBAL into the mother SPEB
364           X= 0.  *
365           Y= 0.        DO I=1,2
366  C         Z= Z - TRPB(3) - MGFR(3)  C DTBAL is the distance along x of the volumes TBAL from the end of TRPB
367           Z=Z-MGFR(3)           DTBAL=3.6
368           N= I           N=I
369           CALL GSPOS('MGFR',N,'SPEB',X,Y,Z,0,'ONLY')           IF(I.EQ.1) THEN
370  C         Y= SPEB(2) - TRPB(2)              X=TRPB(1)-3.6-TBAL(1)
371  C         Z= Z - MGFR(3) - TRPB(3)           ELSE
372  C         N= (I+1)              X=-(TRPB(1)-3.6-TBAL(1))
373  C         IF(I.EQ.5) THEN           ENDIF
374  CC            CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY')           Y=MGFR(2) - 2*TRPB(2)-TBAL(2)
375  C            CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,10,'ONLY')           Z=ZTRPB
376  C         ELSE           CALL GSPOS('TBAL',N,'SPEB',X,Y,Z,0,'ONLY')
377  CC            CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY')        ENDDO
378  C            CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,0,'ONLY')  *
379  C         ENDIF  * Positioning volume TPGU     into the mother MGFR
380           Z=Z-MGFR(3)  *
381        ENDDO        X=0.
382        N=2  C      Z=MGFR(3)-TPGU(3)
383        X=0.        Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3)+TPGI(3)+TPGA(3)+TRPB(3))+
384        Y=MGFR(2) - TRPB(2)       +   TPGU(3)      
385        Z=Z-TRPB(3)        Y=-MGFR(2)+TRPB(2)
386  c      CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,4,'ONLY')        CALL GSPOS('TPGU',N,'MGFR',X,Y,Z,0,'ONLY')
387        CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY')  *
388  *        RETURN
389  * Positioning volume TPGU     into the mother MGFR        END
 *  
       X=0.  
       Z=MGFR(3)-TPGU(3)  
       Y=-MGFR(2)+TRPB(2)  
       CALL GSPOS('TPGU',N,'MGFR',X,Y,Z,0,'ONLY')  
 *  
       RETURN  
       END  

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

  ViewVC Help
Powered by ViewVC 1.1.23