* * $Id: gpspev.F,v 3.7 2005/12/16 10:20:23 cafagna Exp $ * * $Log: gpspev.F,v $ * Revision 3.7 2005/12/16 10:20:23 cafagna * Bug fixed in the new update * * Revision 3.6 2005/12/16 09:13:59 cafagna * New small valume added to the tracker frame * * Revision 3.5 2005/12/13 10:31:29 pam-ba * added a new volume, TPGI, in the spectrometer * * Revision 3.4 2005/12/05 12:15:21 pam-ba * new spectrometer geometry and internal magnetic field * * Revision 3.3 2005/07/25 11:53:21 cafagna * Several updates. See history for details * * 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 TBAL volume * NMED= MAL CALL GSVOLU('TBAL','BOX ',NMED,TBAL, 3,IVOLU) * * Define the MGPA volume * NMED= MAL CALL GSVOLU('MGPA','BOX ',NMED,MGPA, 3,IVOLU) * * Define the TPGA volume * NMED= MN2 CALL GSVOLU('TPGA','BOX ',NMED,TPGA, 3,IVOLU) * * Define the TPGI volume * NMED= MN2 CALL GSVOLU('TPGI','BOX ',NMED,TPGI, 3,IVOLU) * * Define the TPGU volume * NMED= MN2 CALL GSVOLU('TPGU','BOX ',NMED,TPGU, 3,IVOLU) * * Define the TPGD volume * NMED= MN2 CALL GSVOLU('TPGD','BOX ',NMED,TPGD, 3,IVOLU) * * Positioning volume TSPA into the mother TRSL * GLUEX=XGLUE-0.0005 GLUEY=XGLUE N= 1 X= 0. Y= 0. Z= 0. CALL GSPOS('TSPA',N,'TRSL',X,Y,Z,0,'ONLY') C # N= 2 C # C Y= Y - 2.*TSPA(2) C # Y=-TRSL(2)/2 C # CALL GSPOS('TSPA',N,'TRSL',X,Y,Z,0,'ONLY') c ml: 26/11/04: * Positioning volume TRCP into mother TPAS C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one C # Z=-TRPB(3)+0.11+TRCP(3) C # Y=-TRPB(2)+1.5-0.225+TRCP(2) CC end ml. c Z=-TRPB(3)+2*TPAI(3)+TRCP(3) Z=TRPB(3)-2*TPAI(3)-TRCP(3) y=-TPAS(2)+TRCP(2) C # end CAF mod TPASSPACE=TPAS(1)-(3*TRSL(1)+4*TRCP(1)+3*GLUEX) DO I=1,4 CC ml 20/04/05: CC X=-TRPL(1)+(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 C # X=-TRPB(1)+2.29+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1) c ml: 19/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 c X=-TPAS(1)+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1) C Ml. 15/12/05: introducing a space (along x) between the inner part of the c aluminum frame and respectively the first and the last carbon fiber barrel. c It is has been done increasing the dimension of TPAS along x: C X=-TPAS(1)+2*(I-1)*XGLUE+(2*I-1)*TRCP(1)+2*(I-1)*TRSL(1) X=-TPAS(1)+TPASSPACE+2*(I-1)*GLUEX+(2*I-1)*TRCP(1)+ + 2*(I-1)*TRSL(1) CC end ml CALL GSPOS('TRCP',I,'TPAS',X,Y,Z,0,'ONLY') C # end CAF mod ENDDO cc ml 20/04/05: * Positioning volume TRSL into the mother TPAS C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one C # Y=-TRPB(2)+1.5+2*THBP(2)+TRSL(2) C Y=2.75 CC Z= 0. C Z=-0.005 c Z=-TRPB(3)+2*TPAI(3)+TRCP(3) Z=TRPB(3)-2*TPAI(3)-TRCP(3) DO I=1, NTRSL c ml: 20/9/05 introducing the glue between TRCP and the silicon ladders. c X=-TPAS(1)+2*(MOD(I-1,3)+1)*TRCP(1)+ c + (2*(MOD(I-1,3)+1)-1)*TRSL(1) X=-TPAS(1)+TPASSPACE+2*(MOD(I-1,3)+1)*TRCP(1)+ + (2*(MOD(I-1,3)+1)-1)*GLUEX+(2*(MOD(I-1,3)+1)-1)*TRSL(1) IF(I.LE.3) THEN C ml: 22/9/05: c Y=TPAS(2)-TRSL(2) Y=TPAS(2)-0.1485+0.0005-TRSL(2) ELSE C Y=TPAS(2)-3*TRSL(2) Y=TPAS(2)-0.1485-GLUEY-3*TRSL(2) ENDIF CALL GSPOS('TRSL',I,'TPAS',X,Y,Z,0,'ONLY') ENDDO C # end CAF mod ********** cc ml: 20/04/05 * Positioning volume THBP into the mother TPAS C # Caf mod on 19 Jul 2005 all volumes are placed inside the TPAS one C # Y=-TRPB(2)+1.5+THBP(2) C # cc Z= 0. C # Z=-TRPB(3)+0.11+TRCP(3) c ml: 22/9/05: c Y=-TPAS(2)+THBP(2) Y=-TPAS(2)+0.1485+THBP(2) C Z=-0.005 c Z=-TRPB(3)+2*TPAI(3)+TRCP(3) Z=TRPB(3)-2*TPAI(3)-TRCP(3) DO I=1, NTHBP CC X= -TRPL(1) + 2*I*TRCP(1)+(2*I-1)*THBP(1) C # X=-TRPB(1)+2.29+2*I*TRCP(1)+(2*I-1)*THBP(1) c ml: 21/9/05 introducing the glue between the carbon barrel and the silicon c ladders c X=-TPAS(1)+2*I*TRCP(1)+(2*I-1)*THBP(1) X=-TPAS(1)+TPASSPACE+2*I*TRCP(1)+(2*I-1)*THBP(1)+ + (2*(MOD(I-1,3)+1)-1)*GLUEX CALL GSPOS('THBP',I,'TPAS',X,Y,Z,0,'ONLY') ENDDO c end ml. cc ml: 20/04/05 * * Positioning volume TPAI into the mother TPAS * C # Mod By Caf on 19th Jul 2005 all volumes inside the TPAS X=0 Y=-TPAS(2)+TPAI(2) c Z=-TPAS(3)+TPAI(3) Z=TRPB(3)-TPAI(3) C # X=-TRPB(1)+2.29+TPAI(1) C # Y=-TRPB(2)+1.5+2.5+TPAI(2) C # Z=-TRPB(3)+TPAI(3) CALL GSPOS('TPAI',I,'TPAS',X,Y,Z,0,'ONLY') C # end CAF mod * * Positioning volume TPAS into the mother TRPB * C # Mod By Caf on 15th Jul 2005 X=0 Y=-TRPB(2)+1.5+TPAS(2) Z=0 C # X=-TRPB(1)+2.29+TPAS(1) C # Y=-TRPB(2)+1.5+TPAS(2) C # Z=-TRPB(3)+0.11+2*TRCP(3)+TPAS(3) CALL GSPOS('TPAS',I,'TRPB',X,Y,Z,0,'ONLY') c end ml. * * Positioning volume MGPA into the mother MGPL * N= 1 X= 0. Y= 0. Z= 0. CALL GSPOS('MGPA',N,'MGPL',X,Y,Z,0,'ONLY') * * Positioning volume TPGD into the mother MGFR * X=0. Z=-MGFR(3)+TPGD(3) Y=0. CALL GSPOS('TPGD',N,'MGFR',X,Y,Z,0,'ONLY') * * Positioning volume TPGI into the mother MGFR under MGPL * N=1 X=0. Z=-MGFR(3)+2*TPGD(3)+TPGI(3) Y=0. CALL GSPOS('TPGI',N,'MGFR',X,Y,Z,0,'ONLY') * * Positioning volume MGPI into the mother MGPL * N= 1 X= 0. Y= 0. CC ML 10/11/05: Positioning volume MGPI into the mother MGPA Z= 0. CALL GSPOS('MGPI',N,'MGPA',X,Y,Z,0,'ONLY') C Z= -MGFR(3)+2*TPGD(3)+MGPI(3) C CALL GSPOS('MGPI',N,'MGFR',X,Y,Z,0,'ONLY') * * Positioning volume MGPL into the mother MGFR * c ml: 10/11/05 N=1 c Z=-MGFR(3)+MGPL(3) Z=-MGFR(3)+2*(TPGD(3)+TPGI(3))+MGPL(3) CALL GSPOS('MGPL',N,'MGFR',X,Y,Z,0,'ONLY') * * Positioning volume TPGI into the mother MGFR above MGPL * N=2 X=0. Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3))+TPGI(3) Y=0. CALL GSPOS('TPGI',N,'MGFR',X,Y,Z,0,'ONLY') * * Positioning volume TPGA into the mother MGFR * C ML: 10/11/05 N=1 X=0. Y=MGFR(2)-2*(MGFR(2)-TRPB(2))-TPGA(2) C Z=-MGFR(3)+2*MGPL(3)+TPGA(3) C Z=MGFR(3)-2*TPGU(3)-2*TRPB(3)-TPGA(3) Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3)+TPGI(3))+TPGA(3) C Y=-0.75 CALL GSPOS('TPGA',N,'MGFR',X,Y,Z,0,'ONLY') * * Positioning volumes TRPB & MGPL into the mother SPEB * N= 1 X= 0. C Y= SPEB(2) - TRPB(2) Y= -MGFR(2) + TRPB(2) C Z= SPEB(3) - TRPB(3) c Z=-MGFR(3)+2*MGPL(3)+2*TPGA(3)+TRPB(3) C Z=MGFR(3)-2*TPGU(3)-TRPB(3) Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3)+TPGI(3)+TPGA(3))+TRPB(3) C CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY') CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,0,'ONLY') c CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,9,'ONLY') Z=SPEB(3) DO I=1, 5 X= 0. Y= 0. C Z= Z - TRPB(3) - MGFR(3) Z=Z-MGFR(3) N= I CALL GSPOS('MGFR',N,'SPEB',X,Y,Z,0,'ONLY') C Y= SPEB(2) - TRPB(2) C Z= Z - MGFR(3) - TRPB(3) C N= (I+1) C IF(I.EQ.5) THEN CC CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY') C CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,10,'ONLY') C ELSE CC CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,0,'ONLY') C CALL GSPOS('TRPB',N,'MGFR',X,Y,Z,0,'ONLY') C ENDIF Z=Z-MGFR(3) ENDDO N=2 X=0. Y=MGFR(2) - TRPB(2) Z=Z-TRPB(3) ZTRPB=Z c CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,4,'ONLY') CALL GSPOS('TRPB',N,'SPEB',X,Y,Z,10,'ONLY') * * Positioning volume TBAL into the mother SPEB * DO I=1,2 C DTBAL is the distance along x of the volumes TBAL from the end of TRPB DTBAL=3.6 N=I IF(I.EQ.1) THEN X=TRPB(1)-3.6-TBAL(1) ELSE X=-(TRPB(1)-3.6-TBAL(1)) ENDIF Y=MGFR(2) - 2*TRPB(2)-TBAL(2) Z=ZTRPB CALL GSPOS('TBAL',N,'SPEB',X,Y,Z,0,'ONLY') ENDDO * * Positioning volume TPGU into the mother MGFR * X=0. C Z=MGFR(3)-TPGU(3) Z=-MGFR(3)+2*(TPGD(3)+TPGI(3)+MGPL(3)+TPGI(3)+TPGA(3)+TRPB(3))+ + TPGU(3) Y=-MGFR(2)+TRPB(2) CALL GSPOS('TPGU',N,'MGFR',X,Y,Z,0,'ONLY') * RETURN END