C=============================================================================== SUBROUTINE CTVM01 (PRINT, NT,BEAM, PARERRa, IERR) C=============================================================================== C===Description: C Collects/checks track data for the use of CTVMFT for track NT (uses GETTRK), C with bank number LIST(NT), bank type TKBANK(NT), and mass TMASS(NT). C The track/vertex configuration TrkVtx and vertex approximation C XYZVRT(xyz,NV) are communicated through the include file CTVMFT.INC. C The vertex approximation is used to find the RADIUS at which dE/dX and C Coulomb multiple scattering contributions are evaluated. C===Input Arguments: C PRINT If compiled DEBUG, outputs formatted output to unit PRINT C NT Desired track, in the array LIST C BEAM Beam constraint flag, for GETTRK C===Output Arguments: C PARERR Track helix parameter errors C IERR = IJKERR(1) = 3 flags an error getting the track parameters C IJKERR(2) = 1 GETTRK returns an error for this track C 2 the track covariasnce matrix is uninvertable C 3 turns through too large an angle to the vertex C 4 moves too far backwards to the vertex C===Author: C see CTVMFT C------------------------------------------------------------------------------- IMPLICIT NONE #include C===Global Declarations: C---- the following include should be used for all definitions of pi REAL PI C value of PI PARAMETER (PI=3.141592653) REAL TWOPI C 2pi PARAMETER (TWOPI=2.0*PI) REAL HALFPI C pi/2 PARAMETER (HALFPI=0.5*PI) REAL RADDEG C conversion from radians to degrees PARAMETER (RADDEG= 180./PI) REAL DEGRAD C conversion from degrees to radians PARAMETER (DEGRAD= PI/180.) C---- the above include should be used for all definitions of pi C===Local Declarations: INTEGER NT, PRINT, IERR REAL PARERRa(5) LOGICAL BEAM INTEGER I,J,K,L, NV REAL P(5),Q(5,5), HELIX(5,MaxTrk),HWGT(5,5,MaxTrk) REAL RADV, TS,S REAL WORK(MAXDIM) DOUBLE PRECISION RC,XYC(2),U,V, ELM(5,5) CHARACTER*80 STRING C Map the parameter order to CTVMFT form: INTEGER MAP(5) C (Ctg,Crv,Z0,D0,Phi)->(Crv,Phi,Ctg,D0,Z0) DATA MAP / 3,1,5,4,2 / C===Start of Code: C------------------------------------------------------------------------------- C get vertex for this track c----------------------------------------------------------------------- DO NV=1,NVERTX IF (TrkVtx(NT,NV)) GO TO 11 ENDDO 11 RADV = SQRT(XYZVRT(1,NV)**2 + XYZVRT(2,NV)**2) c----------------------------------------------------------------------- C call GETTRK for track data c----------------------------------------------------------------------- IF (LIST(NT).GE.0) THEN CALL GETTRK (LIST(NT),TMASS(NT),RADV, BEAM,K,P,Q, IERR) C Quit on error finding track data bank IF (IERR.NE.0) THEN TKERR(NT) = IERR IJKERR(2) = 1 GOTO 100 ENDIF C save the parameter vector DO I=1,5 K = MAP(I) HELIX(K,NT) = P(I) PARERRa(K) = SQRT(Q(I,I)) DO J=1,5 L = MAP(J) ELM(L,K) = Q(J,I) ENDDO ENDDO C make -and save- the weight matrix CALL DINV(5,ELM,5,WORK,IERR) IF (IERR.NE.0) THEN TKERR(NT) = IERR IJKERR(2) = 2 GO TO 100 END IF DO I=1,5 DO J=1,5 HWGT(J,I,NT) = ELM(J,I) ENDDO ENDDO ENDIF c----------------------------------------------------------------------- C load the fit parameter vector and the corresponding weight matrix c----------------------------------------------------------------------- DO I=1,5 PAR0(I,NT) = HELIX(I,NT) DO J=1,5 G(J,I,NT) = HWGT(J,I,NT) ENDDO ENDDO RC = 0.5/HELIX(1,NT) U = RC + HELIX(4,NT) XYC(1)=-U*SIN(HELIX(2,NT)) XYC(2)= U*COS(HELIX(2,NT)) U = (XYZVRT(1,NV)-XYC(1))/RC V =-(XYZVRT(2,NV)-XYC(2))/RC TS = ATAN2(U,V) - HELIX(2,NT) IF (TS.LT.-PI) THEN TS = TS + TWOPI ELSE IF (TS.GT. PI) THEN TS = TS - TWOPI END IF S = RC*TS c----------------------------------------------------------------------- C it turns too much c----------------------------------------------------------------------- IF (ABS(TS).GT.TRNMAX) THEN IJKERR(2) = 3 C ?what to do? ELSE IF (S.LT.DSMIN) THEN IJKERR(2) = 4 END IF c$$$D IF (IJKERR(2).NE.0) THEN c$$$D WRITE(STRING,1023) NT,LIST(NT), S c$$$D1023 FORMAT(' negative arc length, track',I2,I6 ,F7.2) c$$$D END IF c$$$D IF (PRINT.GT.0) THEN c$$$D IF (NT.EQ.1) WRITE(PRINT,1025) c$$$D WRITE(PRINT,1026) NT,(HELIX(I,NT),I=1,5), S c$$$D1025 FORMAT(/,' Track Initial helix parameters, arc length to Vtx') c$$$D1026 FORMAT(I6,2X,1P,E11.3,0P,F10.4,3F10.4, F12.2) c$$$D END IF c----------------------------------------------------------------------- C===Return to Caller: c----------------------------------------------------------------------- 100 CONTINUE IF (IJKERR(2).NE.0) THEN IERR = 3 IJKERR(1) = 3 IJKERR(3) = NT END IF RETURN END