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

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

  ViewVC Help
Powered by ViewVC 1.1.23