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

  ViewVC Help
Powered by ViewVC 1.1.23