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

Legend:
Removed from v.3.5  
changed lines
  Added in v.3.7

  ViewVC Help
Powered by ViewVC 1.1.23