C ============================================================ SUBROUTINE VER_CABL ( N_CAGES, N_CAGE_TYPE, XYZ_CAGE, x ORIENTATION ) C ============================================================ IMPLICIT NONE C C Description:- C ============= C This subroutine defines the geometry for kapton cables in C the MVD. Only the portion of the kapton cables which covers C the surface of the Si detectors (and hence is directly in C the Phenix acceptance) is included. C C Author:- C ======== C JPSullivan C C Creation Date: 13-Sep-2000 -- based loosely on code C previously in subroutine ver C =========================== C C Revisions:- C =========== C Date Name Description C ---- ---- ---------------------------------------- C C Arguments:- C =========== C INTEGER N_CAGES !total number of cages to be positioned INTEGER N_CAGE_TYPE(*) !0-6 = # Si detectors on cage REAL XYZ_CAGE(3,*) !xyz positions of the cages INTEGER ORIENTATION(*) !0=null rotation, 1=rotated C C Implicit inputs, outputs, side effects:- C ======================================== C C Called by: VER C Calls : GSVOLU, GSATT, GSPOS, GSROTM C Side effects: Numerous changes to Geant GEOM banks. C C Global Specifications:- C ======================= C include 'g77trigdef.inc' include 'gugeom.inc' c include 'gcunit.inc' C include 'fstore.inc' include 'sublink.inc' include 'fpvlink.inc' C C External Specifications:- C ========================= C None C C Local Specifications:- C ====================== REAL VER_DELPHI ! delta phi between ladders (deg) INTEGER NENDS ! # wafers on each end of top, outer layer PARAMETER (VER_DELPHI= 60.) C C*************************************************************************** C C--> Define dimensions of two different types of wafers: C REAL DVWR1(3) ! Box with X, Y, Z REAL DVWR2(3) ! Box with X, Y, Z C C--> Distance from the ladders to the beam axis: C REAL VISLR ! Radius for VISL REAL VOSLR ! Radius for VOSL C C-------------------------------------------------------------------------- C INTEGER COLOR_CABL ! Color (visible/invisible) C C======================================================================== C INTEGER IVOLU ! Error flag returned by GSVOLU INTEGER I,J ! Loop index INTEGER NMED ! Medium number C REAL ANGLE ! Angle for rotation matrix C REAL VER_TH_CABL !thickness of kapton+copper cables INTEGER MED_VER_CABL REAL RCABLE REAL VER_POS_CAB1(3) REAL VER_POS_CAB2(3) REAL VER_SIZ_CAB1(3) REAL VER_SIZ_CAB2(3) INTEGER MYROT(2) INTEGER INDEX_ROT INTEGER N_CABL_LAYERS ! counts layers of cables (0 to 2) INTEGER NCOPY(2) C DATA COLOR_CABL / 157 / C C------------------------------------------------------------------------- C C Executable Statements:- C ======================= C C first pick up the geometry information from the Zebra bank C VISLR = QF(LFV_PARA + OFVA_VISLR) VOSLR = QF(LFV_PARA + OFVA_VOSLR) VER_TH_CABL = QF(LFV_PARA + OFVA_TH_CABL) MED_VER_CABL= NINT(QF(LFV_PARA + OFVA_MED_CABL)) DVWR1(1) = QF(LFV_PARA + OFVA_DVWR1) DVWR1(2) = QF(LFV_PARA + OFVA_DVWR1+1) DVWR1(3) = QF(LFV_PARA + OFVA_DVWR1+2) DVWR2(1) = QF(LFV_PARA + OFVA_DVWR2) DVWR2(2) = QF(LFV_PARA + OFVA_DVWR2+1) DVWR2(3) = QF(LFV_PARA + OFVA_DVWR2+2) C C Now define inner and outer layer cables. The only C difference is that the out layer cables are longer C (y direction in the coordinates below). C VER_SIZ_CAB1(1) = VER_TH_CABL/2. VER_SIZ_CAB1(2) = DVWR1(2) VER_SIZ_CAB1(3) = DVWR1(3) C NMED = MED_VER_CABL CALL GSVOLU ( 'VCAI','BOX ',NMED,VER_SIZ_CAB1,3,IVOLU ) CALL GSATT ( 'VCAI', 'SEEN', 1 ) CALL GSATT ( 'VCAI', 'COLO', COLOR_CABL ) C VER_SIZ_CAB2(1) = VER_TH_CABL/2. VER_SIZ_CAB2(2) = DVWR2(2) VER_SIZ_CAB2(3) = DVWR2(3) C NMED = MED_VER_CABL CALL GSVOLU ( 'VCAO','BOX ', NMED, VER_SIZ_CAB2, 3, IVOLU ) CALL GSATT ( 'VCAO', 'SEEN', 1 ) CALL GSATT ( 'VCAO', 'COLO', COLOR_CABL ) C C two non-null rotations are used below, this array holds C their numbers: C DO I=1,2 MYROT(I) = -1 ! to indicate "not yet defined" NCOPY(I) = 0 ! counts which "copy" of cable is positioned END DO C CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC C C loop over all C-cages and install the cables associated C with each type C DO I=1,N_CAGES C IF ( ORIENTATION(I).EQ.0 ) THEN ANGLE = -60. ! bottom, west INDEX_ROT = 1 ELSE ANGLE = -120. ! bottom, east INDEX_ROT = 2 END IF C IF ( MYROT(INDEX_ROT).LT.0 ) THEN IROT = IROT + 1 MYROT(INDEX_ROT) = IROT CALL GSROTM( IROT, 90.0, ANGLE, 90.0, 90.0+ANGLE, 0.0,0.0 ) END IF C C outer layer, on the bottom, count the number of cables which C should be here: C IF ( N_CAGE_TYPE(I).EQ.5 ) THEN N_CABL_LAYERS = 1 ELSE IF ( N_CAGE_TYPE(I).EQ.6 ) THEN N_CABL_LAYERS = 2 ELSE N_CABL_LAYERS = 0 END IF C IF ( N_CABL_LAYERS.GT.0 ) THEN C RCABLE = VOSLR + 2.0*VER_TH_CABL + DVWR2(1)*4. DO J=1,N_CABL_LAYERS C VER_POS_CAB2(1) = (RCABLE+VER_TH_CABL)*COSD(ANGLE) VER_POS_CAB2(2) = (RCABLE+VER_TH_CABL)*SIND(ANGLE) VER_POS_CAB2(3) = XYZ_CAGE(3,I) C NCOPY(2) = NCOPY(2) + 1 CALL GSPOS ( 'VCAO', NCOPY(2), 'VERT', VER_POS_CAB2(1), x VER_POS_CAB2(2), VER_POS_CAB2(3), x IROT, 'ONLY' ) C RCABLE = RCABLE + 2.0*VER_TH_CABL C END DO END IF C C inner layer, bottom: C IF ( N_CAGE_TYPE(I).EQ.3 ) THEN N_CABL_LAYERS = 1 ELSE IF ( N_CAGE_TYPE(I).GE.4 ) THEN N_CABL_LAYERS = 2 ELSE N_CABL_LAYERS = 0 END IF C IF ( N_CABL_LAYERS.GT.0 ) THEN C RCABLE = VISLR - 2.0*VER_TH_CABL - 2.0*DVWR1(1) DO J=1,N_CABL_LAYERS C VER_POS_CAB1(1) = (RCABLE+VER_TH_CABL)*COSD(ANGLE) VER_POS_CAB1(2) = (RCABLE+VER_TH_CABL)*SIND(ANGLE) VER_POS_CAB1(3) = XYZ_CAGE(3,I) C NCOPY(1) = NCOPY(1) + 1 CALL GSPOS ( 'VCAI', NCOPY(1), 'VERT', VER_POS_CAB1(1), x VER_POS_CAB1(2), VER_POS_CAB1(3), x IROT, 'ONLY' ) C RCABLE = RCABLE - 2.0*VER_TH_CABL C END DO END IF C C now the cables that lay over the middle Si detectors C IF ( N_CAGE_TYPE(I).GE.4 ) THEN N_CABL_LAYERS = 1 ELSE N_CABL_LAYERS = 0 END IF C IF ( N_CABL_LAYERS.GT.0 ) THEN C RCABLE = VISLR - VER_TH_CABL - DVWR1(1)*2. C VER_POS_CAB1(1) = RCABLE - VER_TH_CABL/2. VER_POS_CAB1(2) = 0. VER_POS_CAB1(3) = XYZ_CAGE(3,I) IF ( ORIENTATION(I).EQ.1 ) THEN VER_POS_CAB1(1) = -VER_POS_CAB1(1) END IF C NCOPY(1) = NCOPY(1) + 1 CALL GSPOS ( 'VCAI', NCOPY(1), 'VERT', VER_POS_CAB1(1), x VER_POS_CAB1(2), VER_POS_CAB1(3), x IROTNULL, 'ONLY' ) C END IF C IF ( N_CAGE_TYPE(I).EQ.6 ) THEN N_CABL_LAYERS = 1 ELSE N_CABL_LAYERS = 0 END IF C IF ( N_CABL_LAYERS.GT.0 ) THEN C RCABLE = VOSLR + VER_TH_CABL + DVWR2(1)*4. C VER_POS_CAB2(1) = RCABLE + VER_TH_CABL/2. VER_POS_CAB2(2) = 0. VER_POS_CAB2(3) = XYZ_CAGE(3,I) IF ( ORIENTATION(I).EQ.1 ) THEN VER_POS_CAB2(1) = -VER_POS_CAB2(1) END IF C NCOPY(2) = NCOPY(2) + 1 CALL GSPOS ( 'VCAO', NCOPY(2), 'VERT', VER_POS_CAB2(1), x VER_POS_CAB2(2), VER_POS_CAB2(3), x IROTNULL, 'ONLY' ) C END IF C END DO C RETURN END