ViewVC Help
View File | Revision Log | Show Annotations | Root Listing
root/cvsroot/UserCode/MitCommon/Ctvmft/src/cctvmft.F
Revision: 1.1
Committed: Wed Sep 17 04:01:49 2008 UTC (16 years, 7 months ago) by loizides
Branch: MAIN
CVS Tags: Mit_012i, Mit_012g, Mit_012f, Mit_012e, Mit_012d, Mit_012c, Mit_012b, Mit_012a, Mit_012, Mit_011a, Mit_011, Mit_010a, Mit_010, Mit_009c, Mit_009b, Mit_009a, Mit_009, Mit_008, Mit_008pre2, Mit_008pre1, Mit_006b, Mit_006a, Mit_006, Mit_005, Mit_004
Log Message:
Moved MitVertex contents to MitCommon. MitVertex therefore is obsolute and should not be touched anymore.

File Contents

# User Rev Content
1 loizides 1.1 c $Id:$
2     #include "MitCommon/Ctvmft/interface/cdimensions.hh"
3    
4     C DEC/CMS REPLACEMENT HISTORY, Element CTVMFT.CDF
5     C
6     C 16-Feb-2004 12:00:00 PAUS use .h files and synchronize dimensions
7     C 05-JUN-2003 12:00:00 PAUS allow for multiple single track pointing
8     C 09-JAN-2003 14:30 F. BEDESCHI Introduce beam line constrain option
9     C 15-SEP-2002 17:50 J. GUIMARAES Increased maximum number of tracks
10     C to 50 (MaxTrk)
11     C
12     C 09-AUG-2002 14:13 msmartin : Zero track vertexing supported from
13     C the work of Jonas Radamacker, Mat Martin and Bill Ashmanskas.
14     C *36 27-JUN-1995 16:30:55 BERGE "ooops??? do what I said I wanted to do. How
15     C did I fail?"
16     C *35 27-JUN-1995 15:35:32 BERGE "improve the aesthetic aspects of I*2 handlin
17     C g"
18     C *34 24-JUN-1995 16:59:17 LAMMEL "correct bad FORMAT statments and I*2 intrin
19     C sic functions"
20     C *33 27-MAY-1995 16:56:37 BERGE "protect against negative mass conversion fit
21     C results"
22     C *32 11-MAY-1995 13:43:30 BERGE "fix IJK name"
23     C *31 9-MAY-1995 12:02:02 BERGE "fix first approximation, STV's"
24     C *30 6-APR-1995 12:29:06 BERGE "minus sign screwup"
25     C *29 5-APR-1995 14:00:06 BERGE "bug fixes, error handling rationalization, D
26     C CALC cahnges, debug dump formatting, etcetra"
27     C *28 28-FEB-1995 10:44:28 BERGE "bug fix in vertex/track initialization"
28     C *27 10-FEB-1995 21:13:26 BERGE "modify DCALC to return both Lxy and Lxyz"
29     C *26 12-AUG-1994 13:31:33 BERGE "fix bug in CTVMFA call of GETTRK"
30     C *25 10-FEB-1994 19:08:21 BERGE "fix setting of EXCUSE ME"
31     C *24 28-JAN-1994 14:10:28 BERGE "modify for D_KLINE debugging"
32     C *23 20-DEC-1993 10:41:29 BERGE "modify error handling, improve print routine
33     C "
34     C *22 5-NOV-1993 14:52:42 BERGE "minor bug fixes, idiot-proofing, format impr
35     C ovements, = ?improvements?"
36     C *21 15-SEP-1993 14:02:04 BERGE "another. it's getting to be a bad habit."
37     C *20 15-SEP-1993 13:51:47 BERGE "TRIV"
38     C *19 14-SEP-1993 14:25:56 BERGE "TRIV"
39     C *18 13-SEP-1993 14:05:24 BERGE "assuage Stephan's worries."
40     C *17 12-SEP-1993 12:18:10 BERGE "buffer ERLOGR calls left in DCALC"
41     C *16 12-SEP-1993 11:11:55 BERGE "Bells and whistles. Idiot-proofing."
42     C *15 9-SEP-1993 16:53:46 BERGE "changes to convergence testing, format fixes
43     C "
44     C *14 8-SEP-1993 17:28:12 BERGE "new(er) include file, convergence testing/li
45     C mits"
46     C *13 5-SEP-1993 18:57:50 BERGE "Modify to multi-vertex version"
47     C *12 26-JUL-1993 14:02:45 BERGE "fix GETTRK calling sequence"
48     C *11 6-JUL-1993 14:01:49 BERGE "prepare for new GETTRK calling sequence"
49     C *10 9-JUN-1993 16:49:57 BERGE "correct comment on bank name specification"
50     C *9 12-OCT-1992 15:51:02 BERGE "protect the print routine from nonsense cova
51     C riances"
52     C *8 9-JUL-1992 16:26:35 BERGE "use GETTRK, change mass constraint conventio
53     C n"
54     C *7 19-APR-1992 10:26:30 LAMMEL "re-re-port to rs6000: FORMAT"
55     C *6 3-APR-1992 18:39:51 BERGE "Fix pointing constraint, use DINV"
56     C *5 22-MAR-1992 02:46:43 LAMMEL "re-port to rs6000: FORMAT"
57     C *4 12-MAR-1992 11:10:48 BERGE "fix initialization bug (Gerry Lynch)"
58     C *3 25-FEB-1992 14:54:38 BERGE "bug fixes, error print suppression"
59     C *2 12-JAN-1992 22:24:01 LAMMEL "port to rs6000: FORMAT statement"
60     C *1 17-SEP-1991 13:25:19 BERGE "combined vertex/mass/pointing constrained fi
61     C t"
62     C DEC/CMS REPLACEMENT HISTORY, Element CTVMFT.CDF
63     C===============================================================================
64     SUBROUTINE CCTVMFT (PRINT,LEVPRT,IERR)
65     C===============================================================================
66     C Authors: John Marriner & J.P. Berge
67     C Original Creation: 22 Oct 4004 B.C.E. J.P. Marriner
68     C revision: 1 Sep 2746 A.U.C. J.P. Berge Multiple vertices
69     C revision: 10 Rabi` 1415 A.H. W.J. Ashmanskas Conversion fitting,
70     C 1-track vertex
71     C revision: May 2002 M.S. Martin 0-track vertex
72     C CDF multiple vertex and mass constrained fit package.
73     C This package is documented in CDF/DOC/SEC_VTX/PUBLIC/1996
74     C (which needs revision)
75     C Allows the specification of tracks at one or more vertices, and performs
76     C (geometrical) fits such that at each vertex all tracks at that vertex are
77     C constrained to pass through the same space point ("Vertex fits").
78     C There is a special case of the vertex fit that is designed to treat vertices
79     C with two tracks where the two tracks originate from a photon conversion.
80     C In this case, the two tracks have such a small space opening angle that
81     C the usual vertex fit becomes unstable. For a vertex flagged as a conversion
82     C candidate, extra constraints are imposed. The r-phi opening at the point
83     C where they meet in space. The further requirement that the r-z opening angle
84     C is zero may be optionally imposed.
85     C These fits are not optional. They are always performed.
86     C Allows constraining sub-groups of tracks to specified masses ("mass fit").
87     C Tracks in such a mass fit may be attached to different vertices (consider
88     C the case of the decay Bd -> (psj)(k0). where the Bd mass is constra=ined).
89     C These fits are optional.
90     C Allows constraints such that the momentum sum of tracks at a vertex "points"
91     C to another vertex ("pointing fits").
92     C "Target" vertices may be treated as "primary"; In these cases, vertex
93     C coordinates and covariances are required input and are treated as
94     C measurements in the fit. Such vertices have no attached tracks.
95     C Alternatively, target vertices may be one of the vertices formed from
96     C track intersection fitting in the current fit. Such vertices are considered
97     C "secondary". A secondary vertex that is pointed at a secondary vertex is
98     C a tertiary vertex. There is allowed a special case of a "one-track" vertex
99     C (consider decays Xi -> (lambda)(pi) or B* -> (D0)(pi)). Here the fit
100     C constrains the momentum vector from the tertiary vertex to intersect the
101     C single track at the secondary vertex.
102     C Note that "conversion vertices may point to parent vertices. Note that the
103     C two tracks at such a vertex may appear in a multi-vertex mass-constrained
104     C fit (consider the case Chi -> (psj)(gamma->ee)), but may not appear in any
105     C mass constraint fit restricted only to this vertex.
106     C These fits are optional.
107     C NOTA BENE: Considerable care has been exercized in designing a formatted
108     C dump of the CTVMFT fit results. This dump is activated through setting the
109     C imput parameter PRINT to some non-zero value. If this effort has achieved
110     C its purpose, many points which may remain unclear to the first time user
111     C should be clarified through inspection of dumps of a few fits of interesting
112     C fits. This formattewd output should be printed with 124 columns.
113     C
114     C Additional beam constraint option
115     C =================================
116     C F. Bedeschi, January 2003
117     C
118     C An option to use a beamline constraint in the fit of the primary vertex
119     C has been added. This option does not make sense in the case of secondary
120     C vertex fits and has to be turned on only when fitting the primary with
121     C no additional constraints. The routine is protected and will not function
122     C if those options are selected as well as the bea line constraint.
123     C In case this option is chosen the fit will calculate a result also with
124     C just one track in input.
125     C In order to enable this option the user must do the following:
126     C - set NVERTX = 1
127     C - set Mv=VtxPnt(1,1) = -100 (no pointing constraints when <0. -100 is a new code to
128     C enable this type of fit.)
129     C NB. In this case PRIMARY should be .FALSE. in the code
130     C - set Cvtx(1) = 0 (no mass constraints)
131     C - provide the beamline parameters:
132     C --> assume xv = xb + axb*z, yv = yb + ayb*z, where (xv, yv) is the transverse
133     C beam position at z, (xb, yb) is the transverse beam position at z = 0
134     C as returned by the beam line fit and axb, ayb are the slopes of the beam
135     C line as returned by the beam line fit
136     C --> set XYZPV0 to (xb, yb, 0)
137     C --> set EXYZPV(1,1) = sigma**2 of beam spread in x (~30 - 50 um)**2
138     C EXYZPV(2,2) = sigma**2 of beam spread in y (~30 - 50 um)**2
139     C EXYZPV(3,3) = sigma**2 of beam spread in z (~30 cm)**2
140     C all other elements of EXYZPV should be set to 0
141     C --> set XZSLOPE = axb (this is new parameter in the COMMON/CTVMQ/
142     C YZSLOPE = ayb (this is new parameter in the COMMON/CTVMQ/
143     C
144     C=== End beamline constraint description
145     C
146     C--Input parameters
147     C PRINT If non-zero, dumps formatted fit results to unit PRINT
148     C LEVPRT Controls the level of (optional) printing. Inoperative if PRINT=0.
149     C Avoid this (other than 0,1) unless you know what you are doing.
150     C--Input data communicated through the include file CTVMFT (COMMON /CTVMFC/)
151     C Gross fit specifications (INTEGER);
152     C NTRACK Number of tracks in this fit. (must be at least 2)
153     C NVERTX Number of vertices in this fit (at least one is required)
154     C NMASSC Number of mass constraints (may be zero)
155     C Required topological and constraint information;
156     C TrkVtx(MaxTrk,MaxVtx) LOGICAL
157     C Specifies vertex to which each track is associated.
158     C TrkVtx(Nt,Nv) is .TRUE. if track Nt is attached to vertex Nv.
159     C VtxPnt(MaxVtx,2) INTEGER
160     C Vertex association fit specification.
161     C If Mv=VtxPnt(Nv,1) < 0, no pointing fit is done.
162     C If Mv=VtxPnt(1,1) = -100 a primary vertex fit with beamline constraint
163     C is assumed.
164     C If Mv=VtxPnt(Nv,1) (Nv>Mv) is .GE.0, vertex Nv "points" to vertex Mv.
165     C If Mv=0, the target vertex Mv is supplied as a measurement; the vertex
166     C (x,y,z) together with its 3x3 covariance matrix must be furnished by
167     C the user through the REAL arrays XYZPV0,EXYZPV. "Primary" vertices
168     C are the most usual type of such vertices.
169     C If Mv > 0, the target vertex Mv is a secondary vertex and its coord-
170     C inates are parameters resulting from a track intersection fit.
171     C The kind of "pointing" of vertex Nv to vertex Mv is specified by
172     C setting VtxPnt(Nv,2) to 1, 2, 3 or 4 as desired.
173     C Note that more than one vertex can "point" to the same target vertex.
174     C The constraint is that the sum of the momenta of all the tracks at
175     C vertex Nv together with the summed momenta of all tracks at vertices
176     C which point to Nv must be parallel OR anti-parallel to the vector
177     C from the vertex Nv to vertex Mv. Allowed values of VtxPnt(Nv,2) are;
178     C 1 = constrain pointing of Nv towards Mv in the (R,Phi) plane.
179     C 2 = ALSO constrain pointing in (R,Z) plane (3 dimensional pointing).
180     C 3 = point Nv toward single-track vertex Mv
181     C 4 = point Nv toward zero-track vertex Mv
182     C Note that vertices connected via a charged track are not correctly
183     C handled.
184     C Cvtx(MaxVtx) INTEGER
185     C Conversion constraint fit specification. (The conversion fit
186     C constrains the two tracks at a vertex to be parallel at the vertex.)
187     C 0 = no conversion fit is performed, the vertex is treated normally.
188     C 1 = constrain the track directions in the r-phi plane to be the same
189     C at the radius of the vertex (at the point where the tracks are
190     C copunctual, they are clinear).
191     C 2 = ALSO constrain opening angle to zero in r-z.
192     C TrkMcn(MaxTrk,MaxMcn) LOGICAL
193     C Specifies the tracks that participate in each mass constraint.
194     C Track Nt participates in constraint Nm if TrkMcn(Nt,Nm) is .TRUE.
195     C CMASS(MaxMcn) REAL
196     C The Nmth cluster of tracks is constrained to have mass CMASS(Nm).
197     C Track bank and data specifications;
198     C TKBANK(MaxTrk) CHARACTER*4
199     C Bank name (exempli gratia, 'QTRK','TRKS','SVXS','CTCS') from which
200     C to get each track's helix parameter and covariance data.
201     C These bank names are used in any substantive way only in the data
202     C access subroutine. In CDF, this routine is C$TRK:GETTRK.
203     C LIST (MaxTrk) INTEGER
204     C Bank numbers of the tracks to be used.
205     C TMASS (MaxTrk) REAL
206     C Masses (GeV/c**2) to be associated with the tracks, for purposes of
207     C dE/dX and multiple Coulomb scattering calculations, and for any mass-
208     C constrained fitting.
209     C Output parameter
210     C IERR = 0 (No error), or error code
211     C Returned through the common /CTVMFC/
212     C PAR(5,NTRACK) = The track parameter fit results
213     C XYZVRT(3,0:MaxVtx) The vertex x,y,z fit results.
214     C VMAT(Maxdim,Maxdim) The covariance matrix on the fit parameters
215     C FMCDIF(NMASSC) Residuals of the mass constraints (if used)
216     C PCON(MaxVtx,1) Residual of the (R,Phi) pointing constraint (if used)
217     C PCON(MaxVtx,2) Residual of the (R,Z) pointing constraint (if used)
218     C SANG(MaxVtx,1) sin(ang) between vertex direction and momentum in x-y
219     C SANG(MaxVtx,2) sin(ang) between vertex direction and momentum in rho-z
220     C CHISQR(0:MaxItr) fit Chi Square result(s)
221     C ... other goodies ... Go look at the include file.
222     C Convenient access to VMAT entries for the fit results for vertex and track
223     C parameters is provided by the offset pointer lists VOFF and TOFF.
224     C VOFF(Nv+i) (i=1:3) gives row/column indices for vertex Nv (x,y,z).
225     C TOFF(Nt+i) (i=1:3) gives row/column indices for track Nt (Crv,Phi,Ctg)
226     C Subroutines;
227     C CTVM00 Checks the input for completeness and consistency
228     C CTVMFA Makes the vertex first approximations (uses GETTRK).
229     C CTVM01 Collects the track data (uses GETTRK).
230     C CTVMVF Calculates the derivative contributions for vertex fitting.
231     C CTVMCF conversion fitting.
232     C CTVMPF pointing fittting.
233     C CTVMMF mass constraint fitting.
234     C CTVMPR Prints the fit results, if desired, to output unit PRINT.
235     C-------------------------------------------------------------------------------
236     IMPLICIT NONE
237     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
238     #include "MitCommon/Ctvmft/interface/cctvmft.h"
239     #include "MitCommon/Ctvmft/interface/cctvmfi.h"
240     #include "MitCommon/Ctvmft/interface/cctvmuv.h"
241     #include "MitCommon/Ctvmft/interface/cctvmtu.h"
242     INTEGER PRINT, IERR
243     LOGICAL PRIMARY
244     REAL*8 VXI(MAXDIM)
245     REAL*8 WXYZPV(3,3), SUM
246     REAL*8 LMAT(3,3), LTV(3,3), LTVL(3,3)
247     REAL*8 LTVLX0(3), LTVXV(3), DXBEAM(3)
248     REAL C,PHI,COTH, D,Z, PT, RADV, TWOC, S,TS,TRAD, T1,T2,T3,T4
249     REAL SP,CP, XCYS,XSYC,XC2YC2, SINCS,COSCS,TWOCS, PMAG, XMAG
250     REAL XSVT,YSVT, WORK(MAXDIM), ADDCHIV
251     REAL PARFAC,CUTFAC, DELVS(3,MaxVtx)
252     REAL PCSAVE(MaxVtx,2), MFSAVE(MaxMcn), MFTEST(MaxMcn)
253     REAL STPTK,STEP(5), PARDJF(5,MaxTrk)
254     INTEGER Nv,Mv,Nt,Np,Nm, NvF,NtF,LpF,LmF,LcF
255     INTEGER NITER, NMAXCT,ISCUT,NPC
256     INTEGER I,J,K,L, II(2), I1,I2, IFAIL, IMAX, VERTEX,VRTX
257     INTEGER KTRACK,NPOINT,NCONV, KPRINT
258     C Local variables pertaining to single-track vertices
259     INTEGER STVCOUNT,STVFLAG(MaxVtx)
260     INTEGER BEAM
261     LOGICAL FIRST
262     INTEGER MRUN,MNEV
263     CHARACTER*6 NAME
264     CHARACTER*80 STRING
265     C LEVPRT = print level (0=print disabled)
266     INTEGER LEVPRT
267     REAL ZERO,MINUS,SHOUT, TEST
268     SAVE FIRST,BEAM
269     SAVE NMAXCT, MRUN,MNEV
270     SAVE ZERO,MINUS
271     c DATA ME /0/
272     DATA ZERO /0.0/, MINUS /-1.0/
273     C Maximum number of cut steps allowed in any step
274     DATA NMAXCT / 7 /
275     DATA FIRST /.TRUE./
276     DATA MRUN /-1/, MNEV /-1/
277    
278     CP>>
279     c For tuning only
280     LOGICAL LOST
281     INTEGER NTOT,NERR,NERRC2,NERRLX,NERRLN
282     INTEGER NFIT(0:MAXITR),NOPT(0:MAXITR)
283     REAL MAGN,DV(3),PTVTX,PTTK1,PTTK2,PTTK3
284     REAL DXYZ(3),Dr,Dz,Dl(3)
285     REAL CHI2(0:MAXITR),CRP2(0:MAXITR),LXY(0:MAXITR)
286    
287     INTEGER IXCRP2(3)
288     DATA IXCRP2 / 1, 2, 4 /
289     CP<<
290     C*******************************************************************************
291     DBGPRT = IABS(LEVPRT)
292     C avoid terminating on error in CTVM00
293     C Comment out the following line so that instead of bombing on an error,
294     C CTVMFT returns to VertexFit, so that the error can be properly handled.
295     C Craig Blocker July 19, 2001
296     C EXCUSE = ME
297     IF (LEVPRT.LT.0) THEN
298     EXCUSE =-1
299     END IF
300     IF (PRINT.EQ.0) DBGPRT=0
301     KPRINT = 0
302     IF (PRINT.GT.0 .AND. DBGPRT.GT.10) KPRINT=PRINT
303     C First entrance initializations
304     IF (FIRST) THEN
305     FIRST =.FALSE.
306     C do NOT use beam constrained parameters
307     BEAM = 0
308     WRITE(print,'(A)') ' XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX'
309     WRITE(print,'(A)') ' ---- CCTVMFT First call in program -------'
310     WRITE(print,'(A)') ' XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX'
311     WRITE(print,'(3(A9,I4),/,3(A9,I4))')
312     + ' VtxsMax:',MAXVTX,' TrksMax:',MAXTRK,' ConsMax:',MAXMCN,
313     + ' DimsMax:',MAXDIM,' ItrsMax:',MAXITR,' UDim: ',UDIM
314     WRITE(print,'(A)') ' XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX'
315     END IF
316     IF (MRUN.NE.RUNNUM .OR. MNEV.NE.TRGNUM) THEN
317     C New event, reset track "memory"
318     DO I=1,MaxTrk
319     TKERR(I) =-1.0
320     END DO
321     MRUN = RUNNUM
322     MNEV = TRGNUM
323     END IF
324     IERR = 0
325     DO I=1,3
326     IJKERR(I) = 0
327     END DO
328     NTSCUT = 0
329     CALL VZERO(CHISQR,MaxItr+1)
330     CHISQR(0) =-1.
331     CALL VZERO(CHIV ,MaxVtx+1)
332     CALL VZERO(CHIT ,MaxTrk)
333     CALL VZERO(PARDIF,MaxTrk*5)
334     CALL VZERO(PARDJF,MaxTrk*5)
335     CALL VZERO(PARERR,MaxTrk*5)
336     CALL VZERO(TrkP4, MaxTrk*6)
337     CALL VZERO(DDA, MaxTrk*8)
338     CALL VZERO(XYZVRT,MaxVtx*3+3)
339     CALL VZERO(DELVS, MaxVtx*3)
340     CALL VZERO(PCSAVE,MaxVtx*2)
341     CALL VZERO(LMAT, 2*3*3)
342     CALL VZERO(LTV, 2*3*3)
343     CALL VZERO(LTVL, 2*3*3)
344     CALL VZERO(LTVLX0,2*3)
345     CALL VZERO(LTVXV, 2*3)
346     CALL VZERO(MFSAVE,MaxMcn)
347     CALL VZERO(MFTEST,MaxMcn)
348     CALL VZERO(STVFLAG,MaxVtx)
349     STVCOUNT = 0
350     C Check Input Conditions for illegal conditions
351     C------------------------------------------------------------------------------
352     C Check input specifications
353     CALL CCTVM00 (IERR,WXYZPV)
354     IF (IERR.NE.0) THEN
355     RETURN
356     END IF
357     TRAD = ABS(XYZPV0(1)) + ABS(XYZPV0(2))
358     C flag the appearance of a primary vertex
359     PRIMARY =.FALSE.
360     C check for a primary vertex
361     DO Nv=1,NVERTX
362     IF (VtxPnt(Nv,1).EQ.0) THEN
363     PRIMARY =.TRUE.
364     END IF
365     END DO
366     C primary vertex coordinates - Joao 02/11/03
367     IF (PRIMARY .OR. (TRAD.GT.0.0.AND.VTXPNT(1,1).NE.-100)) THEN
368     DO I=1,3
369     XYZVRT(I,0) = XYZPV0(I)
370     C primary vertex fit displacement
371     DXYZPV(I) = 0.0
372     END DO
373     ENDIF
374     C beamline constraint initializations
375     IF (VTXPNT(1,1) .EQ.-100) THEN
376     DO I = 1,3
377     LMAT(I,I) = 1.0D0
378     ENDDO
379     LMAT(1,3) = -XZSLOPE
380     LMAT(2,3) = -YZSLOPE
381     C Calculate Lt*V**-1
382     CALL VZERO(LTV,2*3*3)
383     DO I = 1,3
384     DO J = 1,3
385     DO K = 1,3
386     LTV(I,J) = LTV(I,J) + LMAT(K,I)*WXYZPV(K,J)
387     ENDDO
388     ENDDO
389     ENDDO
390     C Calculate Lt*V**-1*L
391     CALL VZERO(LTVL,2*3*3)
392     DO I = 1,3
393     DO J = 1,3
394     DO K = 1,3
395     LTVL(I,J) = LTVL(I,J) + LTV(I,K)*LMAT(K,J)
396     ENDDO
397     ENDDO
398     ENDDO
399     D IF (DBGPRT.GT.0) THEN
400     D write(print,5110)
401     D5110 format(1x,'CTVMFT: Beamline initialization done')
402     D write(print,5120)XYZPV0,XZSLOPE, YZSLOPE
403     D5120 format(1x,'Starting vertex x,y,z: ',3(E10.4,2x),
404     D > 'Slopes: x,y: ',2(e10.4,2x))
405     D do i=1,3
406     D write(print,5130)(WXYZPV(i,j), j=1,3)
407     D enddo
408     D5130 format(1x,'WXYZPV: ',3(e10.4,2x))
409     D do i = 1,3
410     D write(print,5140)(ltv(i,j),j=1,3),(ltvl(i,j),j=1,3)
411     D5140 format(1x,'LTV: ',3(E10.4,2x)'LTVL: ',3(e10.4,2x))
412     D enddo
413     D ENDIF
414     ENDIF
415    
416     D IF (DBGPRT.GT.0) THEN
417     D WRITE(PRINT,1000) RUNNUM,TRGNUM, NTRACK,NVERTX,NMASSC
418     D IF (PRIMARY) THEN
419     D WRITE(PRINT,1005) XYZPV0
420     D DO I=1,3
421     D WORK(I) = SQRT(EXYZPV(I,I))
422     D END DO
423     D DO I=1,3
424     D DO J=1,3
425     D VMAT(I,J) = EXYZPV(I,J)/(WORK(I)*WORK(J))
426     D END DO
427     D END DO
428     D WRITE(PRINT,1006) (WORK(I),I=1,3)
429     D WRITE(PRINT,1006) ((VMAT(I,J),I=1,3),J=1,3)
430     D END IF
431     D WRITE(PRINT,1001) (I, LIST(I),TkBank(I),Tmass(I),I=1,NTRACK)
432     D1000 FORMAT('1Event ',I5,'.',I6,'; CTVMFT fit results,'
433     D &,' (Tracks,Vertices,Mass Constraints) ',2(I2,','),I2, /)
434     D1001 FORMAT(' Track',I3,';',I5,A5,F8.3 )
435     D1005 FORMAT( ' Primary vertex ',3F10.4)
436     D1006 FORMAT(16X,3F10.4)
437     D END IF
438     C Vertex fit matrix dimensions;
439     C 3 vertex parameters (x,y,z) per (possible) primary vertex
440     C 3 vertex parameters per secondary vertex
441     C + 0, 1, or 2 "pointing" parameters
442     C + 3 parameters (curvature,phi0,coth(theta0)) per track
443     C + N mass constraints
444     C VOFF(Nv),TOFF(Nt) are offset pointers to ((Vertex,Pointing),Track) parameters
445     C in (the 1st derivative vector, 2nd derivative matrix) VXI, VMAT
446     C VOFF(Nv) points to the start of the 3, 4, or 5 variables for vertex Nv;
447     C vertex Nv (x,y,z, p1,p2)
448     C TOFF(Nt) points to the start of the 3 parameters; track Nt (Crv,Phi,Ctg)
449     C POFF(Lp) points to the start of the Lagrangian multiplier values for the
450     C pointing constraint Lp.
451     C COFF(Lc) points to the start of the Lagrangian multiplier values for the
452     C conversion constraint Lc.
453     C MOFF points to the start of the Lagrangian multiplier values for the
454     C mass constraints
455     C initialize the parameter offset pointer
456     NvF = 0
457     IF (PRIMARY) NvF = 3
458     C offsets to vertex parameters
459     DO Nv=1,NVERTX
460     VOFF(Nv) = NvF
461     NvF = NvF + 3
462     END DO
463     NtF = NvF
464     C offsets to track parameters
465     DO Nt=1,NTRACK
466     TOFF(Nt) = NtF
467     NtF = NtF + 3
468     END DO
469     C count the number of "pointing" constraints
470     NPOINT = 0
471     LpF = NtF
472     C offsets to pointing Lagrangian multipliers
473     DO Nv=1,NVERTX
474     IF (VtxPnt(Nv,1).GE.0) THEN
475     POFF(Nv) = LpF
476     IF (VtxPnt(Nv,2).EQ.1.OR.VtxPnt(Nv,2).EQ.2) THEN
477     NPOINT = NPOINT + VtxPnt(Nv,2)
478     LpF = LpF + VtxPnt(Nv,2)
479     C "one-track vertex"
480     ELSE IF (VtxPnt(Nv,2).EQ.3) THEN
481     IF (STVFLAG(VtxPnt(Nv,1)).EQ.0) THEN
482     C Count number of unique single-track vertices
483     STVFLAG(VtxPnt(Nv,1)) = 1
484     STVCOUNT = STVCOUNT+1
485     ENDIF
486     NPOINT = NPOINT + 2
487     LpF = LpF + 2
488     C "zero-track vertex"
489     ELSE IF (VtxPnt(Nv,2).EQ.4) THEN
490     NPOINT = NPOINT + 2
491     LpF = LpF + 2
492     END IF
493     END IF
494     END DO
495     C count number of "conversion" constraints
496     NCONV = 0
497     LcF = LpF
498     C offsets to zero-opening-angle constraint
499     DO Nv=1,NVERTX
500     C Lagrangian multipliers
501     IF (Cvtx(Nv).GT.0) THEN
502     COFF(Nv) = LcF
503     NCONV = NCONV + Cvtx(Nv)
504     LcF = LcF + Cvtx(Nv)
505     END IF
506     END DO
507     C offset to mass cnst Lagrangian multipliers
508     MOFF = LcF
509     C Fit dimension (number of degrees of freedom)
510     NDOF = 2*NTRACK - 3*NVERTX + NPOINT+NMASSC+NCONV
511     IF (VTXPNT(1,1) .eq. -100)NDOF = NDOF + 3
512     C Dimension of matrix equations
513     MATDIM = NtF + NMASSC+NPOINT+NCONV
514     C Data Collection and Checking, Fit Initialization, Vertex first approximation
515     C------------------------------------------------------------------------------
516     C Loop (backward) over secondary vertices. Ignore for primary vertex fits with
517     C beamline constraint.
518     DO Nv=NVERTX,1,-1
519     IERR = 0
520     CALL CCTVMFA (Nv, PRINT,IERR)
521     IF (IERR.NE.0) THEN
522     WRITE (STRING,2000) IJKERR
523     2000 FORMAT(I4,2I3,' vertex first approximation failure')
524     GO TO 990
525     END IF
526     END DO
527     C------------------------------------------------------------------------------
528     C-------------- Fit iteration start -------------------------------------------
529     ITER = 0
530     NITER = MAXITR
531     C fit iteration (re)entrance point
532     100 CONTINUE
533     D IF (DBGPRT.GT.0) THEN
534     D WRITE(PRINT,1020) ITER
535     D1020 FORMAT(/,' Start Iteration step',I2)
536     D END IF
537     C (re)initialize VXI, VMAT
538     CALL VZERO(VXI, 2*MAXDIM)
539     CALL VZERO(VMAT,2*MAXDIM*(MAXDIM+1))
540     C stuff the primary Vtx covariance into VMAT
541     IF (PRIMARY) THEN
542     DO I=1,3
543     DO J=1,3
544     VMAT(I,J) = WXYZPV(I,J)
545     C (measured - this fit)
546     VXI(I) = VXI(I) - VMAT(I,J)*DXYZPV(J)
547     END DO
548     END DO
549     END IF
550     C Caclulate terms for the vertex fits via track inentersection.
551     DO Nv=NVERTX,1,-1
552     CALL CCTVMVF (KPRINT, Nv, VXI)
553     END DO
554     C accumulate vertex momentum sums, for (possible) pointing constraint fitting
555     C 4-momentum sums for vertex pointing
556     CALL VZERO(VtxP4,MaxVtx*4)
557     DO Nv=NVERTX,1,-1
558     DO Nt=1,NTRACK
559     IF (TrkVtx(Nt,Nv)) THEN
560     DO I=1,4
561     VtxP4(I,Nv) = VtxP4(I,Nv) + TrkP4(Nt,I)
562     END DO
563     END IF
564     C end track loop
565     END DO
566     C does Nv point?
567     Mv = VtxPnt(Nv,1)
568     C tertiary; add P(Nv) to P(Mv)
569     IF (Mv.GT.0) THEN
570     DO I=1,4
571     VtxP4(I,Mv) = VtxP4(I,Mv) + VtxP4(I,Nv)
572     END DO
573     END IF
574     C End vertex loop
575     END DO
576     C calculate terms for "conversion" (zero opening angle) constraint
577     DO Nv=1,NVERTX
578     C conversion constraint, this vertex
579     IF (Cvtx(Nv).GT.0) THEN
580     CALL CCTVMCF (KPRINT, Nv, VXI)
581     END IF
582     C end of the vertex loop
583     END DO
584     C calculate terms for pointing from this vertex towards its parent
585     DO Nv=NVERTX,1,-1
586     C pointing constraint, this vertex
587     IF (VtxPnt(Nv,1).GE.0) THEN
588     CALL CCTVMPF (KPRINT, Nv, VXI)
589     C save the last step quality
590     LpF = POFF(Nv)
591     PCSAVE(Nv,1) = ABS(VXI(LpF+1))
592     PCSAVE(Nv,2) = ABS(VXI(LpF+2))
593     END IF
594     C end of the vertex loop
595     END DO
596     C accumulate momentum sums, for (possible) mass constraint fitting
597     C 4-momentum sums for mass constraints
598     CALL VZERO(McnP4,MaxMcn*4)
599     DO Nm=1,NMASSC
600     DO Nt=1,NTRACK
601     IF (TrkMcn(Nt,Nm)) THEN
602     DO I=1,4
603     McnP4(I,Nm) = McnP4(I,Nm) + TrkP4(Nt,I)
604     END DO
605     END IF
606     END DO
607     END DO
608     C loop over mass constraints
609     DO Nm=1,NMASSC
610     CALL CCTVMMF (KPRINT, Nm, VXI)
611     LmF = MOFF
612     MFSAVE(Nm) = ABS(VXI(LmF+Nm))
613     END DO
614     C
615     C Additional terms for beamline constraint
616     C
617     IF (VTXPNT(1,1) .EQ. -100) THEN
618     D IF (DBGPRT.GT.0) THEN
619     D write(print,5150)NTRACK, (XYZVRT(i,1),i=1,3)
620     D5150 format(1x,'Ntracks: ',i3,
621     D > 'Vertex before iteration: ',3(e10.4,2x))
622     D ENDIF
623     C Update VMAT
624     DO I = 1,3
625     DO J = 1,3
626     VMAT(I,J) = VMAT(I,J) + LTVL(I,J)
627     ENDDO
628     ENDDO
629     C Update VXI
630     CALL VZERO(LTVXV, 2*3)
631     CALL VZERO(LTVLX0,2*3)
632     DO I = 1,3
633     DO J = 1,3
634     LTVXV(I) = LTVXV(I) + LTV(I,J)*XYZPV0(J)
635     LTVLX0(I) = LTVLX0(I) + LTVL(I,J)*XYZVRT(J,1)
636     ENDDO
637     VXI(I) = VXI(I) + LTVXV(I) - LTVLX0(I)
638     ENDDO
639     ENDIF
640     C End of the derivative accumulation phase; Now solve matrix equations
641     C Find solution without finding inverse
642     IF (ITER.EQ.0) THEN
643     CALL MYDEQN (MATDIM,VMAT,MAXDIM,WORK,IFAIL,1,VXI)
644     C Find solution + covariance matrix
645     ELSE
646     CALL MYDEQINV(MATDIM,VMAT,MAXDIM,WORK,IFAIL,1,VXI)
647     ENDIF
648     IF (IFAIL.NE.0) THEN
649     IERR = 9
650     IJKERR(2) = 1
651     WRITE(STRING,2030)
652     2030 FORMAT(' singular solution matrix')
653     RETURN
654     END IF
655     C Check the step just taken for acceptability and for possible convergence
656     C Initialize cut steps counter
657     ISCUT = 0
658     C Step size scale factor - normally 1
659     CUTFAC = 1.0
660     C Fraction of the step already taken
661     PARFAC = 0.0
662     C Check that track turning angles to the new vertex points are acceptable
663     110 CONTINUE
664     C x,y for this vertex, this step cut factor
665     DO 150 Nv=1,NVERTX
666     NvF = VOFF(Nv)
667     XSVT = XYZVRT(1,Nv) + CUTFAC*VXI(NvF+1)
668     YSVT = XYZVRT(2,Nv) + CUTFAC*VXI(NvF+2)
669     C track loop, checking turning angle
670     DO 140 Nt=1,NTRACK
671     IF (.NOT.TrkVtx(Nt,Nv)) GO TO 140
672     NtF = TOFF(Nt)
673     C = PAR0(1,Nt) + PARDIF(1,Nt) + CUTFAC*VXI(NtF+1)
674     PHI = PAR0(2,Nt) + PARDIF(2,Nt) + CUTFAC*VXI(NtF+2)
675     TS = 2.0*C*(XSVT*COS(PHI)+YSVT*SIN(PHI))
676     C track turns too much, cut step size
677     IF (ABS(TS).GT.TRNMAX) THEN
678     ISCUT = ISCUT+1
679     NTSCUT = NTSCUT + 1
680     C maximum number of cut steps exceeded
681     IF (ISCUT.GT.NMAXCT) THEN
682     IERR = 9
683     IJKERR(2) = 2
684     IJKERR(3) = ITER
685     WRITE(STRING,2050) IJKERR
686     2050 FORMAT(' too many cut steps', I5,2I3)
687     GO TO 990
688     END IF
689     CUTFAC = 0.5*(CUTFAC-PARFAC)
690     D IF (DBGPRT.GT.1) THEN
691     D WRITE(PRINT,1050) ITER,ISCUT,Nv,Nt,XSVT,YSVT
692     D1050 FORMAT(' Iter',I2,' Cut',I2,', Nv,Nt ',I1,I4,2F10.4)
693     D END IF
694     GO TO 110
695     END IF
696     140 CONTINUE
697     150 CONTINUE
698     PARFAC = PARFAC+CUTFAC
699     C Provisionally acceptable step;
700     C Update all the fit parameters and calculate Chi Square, this step
701     C Re-initialize, recompute momentum sums with the new step results
702     C Update primary vertex coordinates
703     IF (PRIMARY) THEN
704     DO I=1,3
705     DXYZPV(I) = DXYZPV(I) + CUTFAC*VXI(I)
706     XYZVRT(I,0) = XYZPV0(I) + DXYZPV(I)
707     END DO
708     END IF
709     C Contribution from the "primary" vertex
710     CHIV(0) = 0.0
711     IF (PRIMARY) THEN
712     DO I=1,3
713     DO J=1,3
714     CHIV(0)= CHIV(0) + DXYZPV(I)*WXYZPV(I,J)*DXYZPV(J)
715     END DO
716     END DO
717     END IF
718     CHISQR(ITER) = CHIV(0)
719     C Update secondary vertex coordinates
720     DO Nv=1,NVERTX
721     Nvf = VOFF(Nv)
722     DO I=1,3
723     XYZVRT(I,Nv) = XYZVRT(I,Nv) + CUTFAC*VXI(NvF+I)
724     Mv = VtxPnt(Nv,1)
725     C vertex separation vector
726     IF (Mv.GE.0) THEN
727     DELVS(I,Nv) = XYZVRT(I,Mv) - XYZVRT(I,Nv)
728     END IF
729     END DO
730     END DO
731     D IF (DBGPRT.GT.0) THEN
732     D write(print,5160)NTRACK, (XYZVRT(i,1),i=1,3)
733     D5160 format(1x,'Ntracks: ',i3,
734     D > ', Vertex after iteration: ',3(e10.4,2x))
735     D END IF
736     DO 210 Nv=1,NVERTX
737     CHIV(Nv) = 0.0
738     C Update the track parameters
739     DO 210 Nt=1,NTRACK
740     IF (.NOT.TrkVtx(Nt,Nv)) GO TO 210
741     NtF = TOFF(Nt)
742     C half curvature step
743     PARDIF(1,Nt) = PARDIF(1,Nt) + CUTFAC*VXI(NtF+1)
744     C phi step
745     PARDIF(2,Nt) = PARDIF(2,Nt) + CUTFAC*VXI(NtF+2)
746     C cot(theta) step
747     PARDIF(3,Nt) = PARDIF(3,Nt) + CUTFAC*VXI(NtF+3)
748     C new half curvature
749     C = PAR0(1,Nt) + PARDIF(1,Nt)
750     C new phi
751     PHI = PAR0(2,Nt) + PARDIF(2,Nt)
752     C new coth(theta)
753     COTH = PAR0(3,Nt) + PARDIF(3,Nt)
754     SP = SIN(PHI)
755     CP = COS(PHI)
756     C Xsv*cos(phi) + Ysv*sin(phi), -Xsv*sin(phi) + Ysv*cos(phi), 2C
757     XCYS = XYZVRT(1,Nv)*CP + XYZVRT(2,Nv)*SP
758     XSYC =-XYZVRT(1,Nv)*SP + XYZVRT(2,Nv)*CP
759     TWOC = 2.0*C
760     C 10/23/02 Protect against TWOC begin zero. Craig Blocker
761     c?? if(twoc .eq. 0.) then
762     IF (ABS(TWOC) .LT. 1E-24) THEN
763     S = XCYS
764     else
765     S = ASIN(TWOC*XCYS)/TWOC
766     endif
767     TS = TWOC*XCYS
768     TRAD = SQRT((1.-TS)*(1.+TS))
769     C Constrained d0
770     C 10/23/02 Protect against C being zero. Craig Blocker
771     c?? if(c .eq. 0.) then
772     IF (ABS(C) .LT. 1E-24) THEN
773     D = XSYC
774     else
775     D = XSYC - SIN(C*S)**2/C
776     endif
777     C Constrained z0
778     Z = XYZVRT(3,Nv) - COTH*S
779     C fit d0 - CTC fit d0
780     PARDIF(4,Nt) = D - PAR0(4,Nt)
781     C fit z0 - CTC fit z0
782     PARDIF(5,Nt) = Z - PAR0(5,Nt)
783     C 1/20/04 Protect against C being zero. Here it is not
784     C clear what to set PT to. I chose 999. GeV since this is
785     C a very large Pt in CDF, this is roughly a standard deviation
786     C from infinite, and should be clearly recognizable. Craig Blocker
787     c?? if(c .eq. 0.) then
788     IF (ABS(C) .LT. 1E-24) THEN
789     PT = 999.
790     else
791     PT = PSCALE/ABS(C)
792     endif
793     C x component of momentum
794     TrkP4(Nt,1) = PT*(CP*TRAD-SP*TS)
795     C y component of momentum
796     TrkP4(Nt,2) = PT*(SP*TRAD+CP*TS)
797     C z component of momentum
798     TrkP4(Nt,3) = PT*COTH
799     C Transverse momentum
800     TrkP4(Nt,5) = PT
801     C total momentum
802     TrkP4(Nt,6) = SQRT(PT**2+TrkP4(Nt,3)**2)
803     C energy
804     TrkP4(Nt,4) = SQRT(TrkP4(Nt,6)**2+TMASS(NT)**2)
805     C Calculate contribution to chi-squared for this track
806     CHIT(Nt) = 0.0
807     C Loop over rows of the weight matrix
808     DO I=1,5
809     C Loop over columns of the weight matrix
810     DO J=1,5
811     CHIT(Nt) = CHIT(Nt) + PARDIF(I,Nt)*G(J,I,Nt)*PARDIF(J,Nt)
812     END DO
813     END DO
814     CHIV(Nv) = CHIV(Nv) + CHIT(Nt)
815     CHISQR(ITER) = CHISQR(ITER) + CHIT(Nt)
816     C End the loop on tracks
817     210 CONTINUE
818     C Beamline constraint contribution
819     IF(VTXPNT(1,1).EQ.-100)THEN
820     DO I = 1,3
821     DXBEAM(I) = -XYZPV0(I)
822     DO J = 1,3
823     DXBEAM(I) = DXBEAM(I) + LMAT(I,J)*XYZVRT(J,1)
824     ENDDO
825     ENDDO
826     ADDCHIV = 0.0
827     DO I = 1,3
828     DO J = 1,3
829     ADDCHIV = ADDCHIV + DXBEAM(I)*DXBEAM(J)*WXYZPV(I,J)
830     ENDDO
831     ENDDO
832     CHIV(NV) = CHIV(NV) + ADDCHIV
833     CHISQR(ITER) = CHISQR(ITER) + ADDCHIV
834     ENDIF
835     CALL VZERO(VtxP4,MaxVtx*4)
836     CALL VZERO(McnP4,MaxMcn*4)
837     DO Nt=1,NTRACK
838     DO Nv=NVERTX,1,-1
839     IF (TrkVtx(Nt,Nv)) THEN
840     C accumulate vertex sums
841     DO I=1,4
842     VtxP4(I,Nv) = VtxP4(I,Nv) + TrkP4(Nt,I)
843     END DO
844     END IF
845     END DO
846     C accumulate mass constraint sums
847     DO Nm=1,NMASSC
848     IF (TrkMcn(Nt,Nm)) THEN
849     DO I=1,4
850     McnP4(I,Nm) = McnP4(I,Nm) + TrkP4(Nt,I)
851     END DO
852     END IF
853     END DO
854     END DO
855     DO Nv=1,NVERTX
856     C does Nv point?
857     Mv = VtxPnt(Nv,1)
858     C tertiary; add P(Nv) to P(Mv)
859     IF (Mv.GT.0) THEN
860     DO I=1,4
861     VtxP4(I,Mv) = VtxP4(I,Mv) + VtxP4(I,Nv)
862     END DO
863     END IF
864     END DO
865     C Check the quality of satisfaction of the pointing constraints, this step
866     DO 220 Nv=1,NVERTX
867     Mv = VtxPnt(Nv,1)
868     IF (Mv.LT.0) GO TO 220
869     C IMAX points to larger PSUM component (1=x,2=y)
870     IMAX = 1
871     IF (ABS(VtxP4(1,Nv)).LT.ABS(VtxP4(2,Nv))) IMAX = 2
872     NPC = VtxPnt(Nv,2)
873     IF (NPC.EQ.3) NPC = 2
874     IF (NPC.EQ.4) NPC = 2
875     DO Np=1,NPC
876     IF (Np.EQ.1) THEN
877     C Residual of first pointing constraint, this step
878     SUM = VtxP4(1,Nv)*DELVS(2,Nv) - VtxP4(2,Nv)*DELVS(1,Nv)
879     PMAG = SQRT(VtxP4(1,Nv)**2+VtxP4(2,Nv)**2)
880     XMAG = SQRT(DELVS(1,Nv)**2+DELVS(2,Nv)**2)
881     ELSE
882     C Residual of second pointing constraint, this step
883     SUM = DELVS(3,Nv)*VtxP4(IMAX,Nv) - DELVS(IMAX,Nv)*VtxP4(3,Nv)
884     PMAG = SQRT(VtxP4(IMAX,Nv)**2 + VtxP4(3,Nv)**2)
885     XMAG = SQRT(DELVS(IMAX,Nv)**2+DELVS(3,Nv)**2)
886     END IF
887     PCON(Nv,Np) = SUM
888     C Check for very small vertex separation
889     IF (XMAG .GT. .001) THEN
890     C OK. Get sin(angle)
891     SANG(Nv,Np) = PCON(Nv,Np)/(PMAG*XMAG)
892     ELSE
893     SANG(Nv,Np) = 2.0
894     ENDIF
895     END DO
896     C end vertex loop
897     220 CONTINUE
898     C Check the quality of satisfaction pf the mass constraints, this step
899     DO Nm=1,NMASSC
900     C Residual of mass constraint.
901     SUM = SQRT(McnP4(1,Nm)**2+McnP4(2,Nm)**2+McnP4(3,Nm)**2)
902     SUM = (McnP4(4,Nm)+SUM) * (McnP4(4,Nm)-SUM)
903     IF (SUM.LE.0.0) THEN
904     SUM = 0.0
905     ELSE
906     SUM = SQRT(SUM)
907     END IF
908     FMCDIF(Nm) = (SUM + CMASS(Nm)) * (SUM - CMASS(Nm))
909     MFTEST(Nm) = 0.5 * FMCDIF(Nm)
910     C Convert to Delta m in MeV from Delta m**2 in GeV
911     FMCDIF(Nm) = 500.*FMCDIF(Nm)/CMASS(Nm)
912     END DO
913     C Check the improvements(?) in pointing and mass constraints, this step
914     C If step size is too large the constraints will not be satisfied.
915     C If there is a problem, the step size will be halved
916     C Check pointing constraints
917     DO 230 Nv=1,NVERTX
918     Mv = VtxPnt(Nv,1)
919     IF (Mv.LT.0) GO TO 230
920     NPC = VtxPnt(Nv,2)
921     IF (NPC.EQ.3) NPC = 2
922     IF (NPC.EQ.4) NPC = 2
923     DO I=1,NPC
924     C = PCON(Nv,I) / (PCSAVE(Nv,I) + 0.001)
925     IF ((ABS(C).GT.1.0) .AND. (ABS(SANG(Nv,I)).GT..01)) THEN
926     D IF (DBGPRT.GT.1) THEN
927     D WRITE(PRINT,1051) ITER,ISCUT,Nv,Mv,I,C,SANG(Nv,I)
928     D1051 FORMAT(' Iter',I2,' Cut',I2,', Nv,Mv,I',2I3,I4,2F10.5)
929     D END IF
930     GO TO 250
931     END IF
932     END DO
933     C End vertex loop
934     230 CONTINUE
935     C Check mass constraints
936     DO Nm=1,NMASSC
937     C = ABS(MFTEST(Nm) / (MFSAVE(Nm) + 0.1))
938     IF (C.GT.1.0) THEN
939     D IF (DBGPRT.GT.1) THEN
940     D WRITE(PRINT,1052) ITER,ISCUT,Nm,C,MFTEST(Nm)
941     D1052 FORMAT(' Iter',I2,' Cut',I2,', Nm',I2,2F10.5)
942     D END IF
943     GO TO 250
944     END IF
945     END DO
946     GO TO 300
947     250 CONTINUE
948     C Count a cut step
949     ISCUT = ISCUT + 1
950     NTSCUT = NTSCUT + 1
951     C maximum number of cut steps exceeded
952     IF (ISCUT .GT. NMAXCT) THEN
953     IERR = 9
954     IJKERR(2) = 3
955     IJKERR(3) = ITER
956     WRITE(STRING,2050) IJKERR
957     GO TO 990
958     END IF
959     C Prepare to subtract off 1/2 step size taken
960     CUTFAC = -0.5*PARFAC
961     GO TO 110
962     C Accept this step
963     300 CONTINUE
964     CHISQR(0) = CHISQR(ITER)
965     STPTK = 1.0
966     IF (ITER.GT.0) THEN
967     STPTK = 0.0
968     DO NT=1,NTRACK
969     C make the difference between this step and the previous
970     DO I=1,5
971     PARDJF(I,NT) = PARDIF(I,NT) - PARDJF(I,NT)
972     STEP(I) = PARDJF(I,NT)/PARERR(I,NT)
973     STPTK = AMAX1(STPTK,ABS(STEP(I)))
974     END DO
975     END DO
976     END IF
977     D IF (DBGPRT.GT.1) THEN
978     D C = AMIN1(CHISQR(0),9999.0)
979     D L = 1
980     D IF (PRIMARY) L=0
981     D DO I=L,NVERTX
982     D WORK(I) = AMIN1(CHIV(I),999.0)
983     D END DO
984     D IF (NVERTX.EQ.1 .AND. L.EQ.1) THEN
985     D WRITE(PRINT,1070) stptk, C
986     D1070 FORMAT(/,' StpTk ',F8.3,'; ChiSqr =',F7.2)
987     D ELSE
988     D WRITE(PRINT,1071) stptk, C, (I,WORK(I),I=L,NVERTX)
989     D1071 FORMAT(/,' StpTk ',F8.3,'; ChiSqr =',F7.2, 4(3X,'ChiV',I2,F7.2) )
990     D END IF
991     D IF (ITER.EQ.0) GO TO 500
992     D DO NT=1,NTRACK
993     D WORK(Nt) = AMIN1(CHIT(Nt),999.0)
994     D DO I=1,5
995     D STEP(I) = PARDJF(I,NT)/PARERR(I,NT)
996     D END DO
997     D WRITE(PRINT,1075) nt, WORK(Nt), STEP
998     D1075 FORMAT(i5,F10.4,2x,5F10.6)
999     D END DO
1000     D END IF
1001     C Check for step acceptability
1002     500 CONTINUE
1003     CP>>
1004     c
1005     c Do the calculation myself here
1006     c
1007     DO I=1,3 ! vertex vector
1008     DV(I) = XYZVRT(I,1) - XYZPV0(I)
1009     ENDDO
1010     MAGN = 0.0
1011     LXY(ITER) = 0.0
1012     DO I=1,2 ! length of momentum, Xvtx dot Ptvtx
1013     MAGN = MAGN + VtxP4(I,1)*VtxP4(I,1)
1014     LXY(ITER) = LXY(ITER) + VtxP4(I,1)*DV(I)
1015     ENDDO
1016     LXY (ITER) = LXY(ITER)/SQRT(MAGN) ! project to unit length
1017     CHI2(ITER) = CHISQR(0) ! fit quality in 3d
1018     CRP2(ITER) = 0.0 ! fit quality quasi in 2d
1019     DO I=1,NTRACK
1020     DO J=1,3
1021     DO K=1,3
1022     CRP2(ITER) = CRP2(ITER) +
1023     & PARDIF(IXCRP2(J),I)*G(IXCRP2(K),IXCRP2(J),I)*
1024     & PARDIF(IXCRP2(K),I);
1025     ENDDO
1026     ENDDO
1027     ENDDO
1028     c
1029     c Implement early termination
1030     c
1031     IF (ITER.EQ.0) THEN
1032     IF ((C20MAX.GT.0.0 .AND. CRP2(0).GT.C20MAX) .OR.
1033     & ( LXY(0).LT.LXY0MN) ) THEN
1034     IERR = 9
1035     GOTO 990
1036     ENDIF
1037     ENDIF
1038     IF (ITER.EQ.1) THEN
1039     IF ((C21MAX.GT.0.0 .AND. CRP2(1).GT.C21MAX) .OR.
1040     & ( LXY(1).LT.LXY1MN) ) THEN
1041     IERR = 9
1042     GOTO 990
1043     ENDIF
1044     ENDIF
1045     CP<<
1046     IF (ITER.EQ.0) GO TO 550
1047    
1048     IF (STPTK.LT.0.1) THEN
1049     C accept the convergence
1050     GO TO 900
1051     ELSE IF (ITER.GE.MAXITR) THEN
1052     C "convergence", sort of. Accept the stinker?
1053     IF (STPTK.LT.0.2) THEN
1054     GO TO 900
1055     ELSE
1056     STPTK = AMIN1(STPTK,9999.0)
1057     IERR = 9
1058     IJKERR(2) = 4
1059     WRITE(STRING,2090) ITER,StpTk,CHISQR(0)
1060     2090 FORMAT('; Convergence failure, Itr =',I2,'; StpTk ',F7.2
1061     &, ' ChiSqr(i) ', 1P,E9.2)
1062     GO TO 990
1063     END IF
1064     ELSE
1065     IF (ITER.GT.2) THEN
1066     C after the 2nd step, if the "ChiSquare"
1067     TEST = FLOAT(NDOF) * chisqmx
1068     C is >15 "standard deviations", and if
1069     IF (CHISQR(0).GT.TEST) THEN
1070     C the last step was did not do much good
1071     IF (STPTK.GT.0.5) THEN
1072     STPTK = AMIN1(STPTK,9999.0)
1073     C give up in disgust
1074     IERR = 9
1075     IJKERR(2) = 5
1076     WRITE(STRING,2095) ITER,StpTk,CHISQR(0)
1077     2095 FORMAT('; Bad convergence, Itr =',I2,'; StpTk ',F7.2
1078     &, ' ChiSqr(i) ', 1P, 6E9.2)
1079     GO TO 990
1080     END IF
1081     END IF
1082     END IF
1083     END IF
1084     550 CONTINUE
1085     C return for the next iteration step
1086     DO NT=1,NTRACK
1087     C save the last step on this track
1088     DO I=1,5
1089     PARDJF(I,NT) = PARDIF(I,NT)
1090     END DO
1091     END DO
1092     ITER = ITER + 1
1093     GO TO 100
1094     C Successful Return
1095     C------------------------------------------------------------------------------
1096     900 CONTINUE
1097     C final track parameters
1098     DO Nt=1,NTRACK
1099     DO I=1,5
1100     PAR(I,NT) = PAR0(I,Nt) + PARDIF(I,Nt)
1101     END DO
1102     D IF (DBGPRT.GT.0) THEN
1103     D write(print,5170)NT,(par(i,nt),i=1,5)
1104     D5170 format(1x,'Final track ',i3,' params ',5(1x,e10.4))
1105     D ENDIF
1106     END DO
1107     IF (PRINT.GT.0) THEN
1108     CALL CCTVMPR(PRINT,DBGPRT,PARERR)
1109     END IF
1110     cccCP>>
1111     ccc
1112     ccc Book keeping for optimization
1113     ccc
1114     cccc WRITE(*,*)
1115     cc NTOT = NTOT + 1
1116     cc NFIT(ITER) = NFIT(ITER) + 1
1117     ccc
1118     ccc check general quality and reject accordingly
1119     cc LOST = .FALSE.
1120     cc IF ((C20MAX.GT.0.0 .AND. CRP2(0).GT.C20MAX) .OR.
1121     cc & (C21MAX.GT.0.0 .AND. CRP2(1).GT.C21MAX) .OR.
1122     cc & LXY(0).LT.LXY0MN .OR. LXY(1).LT.LXY1MN ) THEN
1123     cc NOPT(0) = NOPT(0) + 1
1124     cc IF (CRP2(ITER).LT.30.0 .AND. LXY(ITER).GT.0.015) THEN
1125     cc PTVTX = SQRT(VtxP4(1,1)*VtxP4(1,1)+VtxP4(2,1)*VtxP4(2,1))
1126     cc PTTK1 = SQRT(TRKP4(1,1)*TRKP4(1,1)+TRKP4(1,2)*TRKP4(1,2))
1127     cc PTTK2 = SQRT(TRKP4(2,1)*TRKP4(2,1)+TRKP4(2,2)*TRKP4(2,2))
1128     cc PTTK3 = SQRT(TRKP4(3,1)*TRKP4(3,1)+TRKP4(3,2)*TRKP4(3,2))
1129     cc WRITE(*,'(A,12F11.5)') ' ERROR -- !! Lost Vertex !! ',
1130     cc & CHI2(0),CHI2(1),CRP2(0),CRP2(1),LXY(0),
1131     cc & CHI2(ITER),CRP2(ITER),LXY(ITER),PTVTX,PTTK1,PTTK2,PTTK3
1132     cc NERR = NERR + 1
1133     cc LOST = .TRUE.
1134     cc ENDIF
1135     cc ELSE
1136     cc NOPT(ITER) = NOPT(ITER) + 1
1137     cc ENDIF
1138     ccc
1139     ccc start with too large chi2
1140     cc IF (CRP2(0).GT.C20MAX .OR. CRP2(1).GT.C21MAX) THEN
1141     cc NOPT(0) = NOPT(0) + 1
1142     cc IF ((CHI2(ITER).LT.30)) THEN
1143     cc NERRC2 = NERRC2 + 1
1144     cc ENDIF
1145     ccc
1146     ccc next too small Lxy
1147     cc ELSEIF (LXY(0).LT.LXY0MN .OR. LXY(1).LT.LXY1MN) THEN
1148     cc NOPT(0) = NOPT(0) + 1
1149     cc IF (LXY(ITER).GT.0.015) THEN
1150     cc NERRLN = NERRLN + 1
1151     cc ENDIF
1152     cc ENDIF
1153     ccc
1154     ccc Printout the stuff
1155     ccc
1156     ccc WRITE(*,'(A,3F10.5)') 'VtxPv ',XYZPV0(1),XYZPV0(2),XYZPV0(3)
1157     ccc WRITE(*,'(A,3F10.5)') 'Vtx1 ',XYZVRT(1,1),XYZVRT(2,1),XYZVRT(3,1)
1158     ccc WRITE(*,'(A,3F10.5)') 'P ',VTXP4 (1,1),VTXP4 (2,1),VTXP4 (3,1)
1159     ccc
1160     ccc Test 'no fit left behind' policy
1161     ccc
1162     cc IF (LOST) THEN
1163     cc WRITE(*,'(3(A,F10.5))')
1164     cc & ' iChi2: ',CHI2(0),' iCrp2: ',CRP2(0),' iLxy: ',LXY(0)
1165     cc DO I=1,ITER
1166     cc WRITE(*,'(3(A,F10.5))')
1167     cc & ' dChi2: ',CHI2(I)-CHI2(0),' dCrp2: ',CRP2(I)-CRP2(0),
1168     cc & ' dLxy: ',LXY(I)-LXY(0)
1169     cc ENDDO
1170     cc WRITE(*,'(3(A,F10.5))')
1171     cc & ' fChi2: ',CHI2(ITER),' fCrp2: ',CRP2(ITER),
1172     cc & ' fLxy: ',LXY (ITER)
1173     cc ENDIF
1174     cc
1175     cc IF (MOD(NTOT,10000) .EQ. 0) THEN
1176     cc WRITE(*,'(12I9)') NTOT,(NFIT(I),I=0,MAXITR)
1177     cc WRITE(*,'(12I9)') NERR,(NOPT(I),I=0,MAXITR)
1178     cc WRITE(*,'( 3I9)') NERRC2,NERRLX,NERRLN
1179     cc ENDIF
1180     ccCP<<
1181     C Check for peculiar case of non-positive diagonal matrix elements, which
1182     C should never happen, but if it happens, better to report it than to
1183     C let it slip by unnoticed. All errors of this sort should be reported
1184     C immediately to the guilty parties.
1185     DO I = 1,TOFF(NTRACK)+3
1186     IF (VMAT(I,I).LE.0) THEN
1187     STRING = 'SERIOUS problem with ill-formed covariance matrix'
1188     IERR = 9
1189     IJKERR(1) = 9
1190     IJKERR(2) = 9
1191     CALL CERROR('CTVMFT',IERR,STRING)
1192     IF (PRINT.GT.0) WRITE (PRINT,*) MRUN,MNEV,I,VMAT(I,I)
1193     GOTO 999
1194     END IF
1195     END DO
1196     RETURN
1197     C Error Return
1198     C-------------------------------------------------------------------------------
1199     990 CONTINUE
1200     IF (IERR.NE.0) THEN
1201     IJKERR(1) = IERR
1202     NAME = 'CTVMFT'
1203     ccc write(*,9001) name,ierr,string
1204     ccc 9001 format(1x,A,": Ierr = ",i3," => ",A)
1205     D IF (PRINT.GT.0 .OR. IERR.GT.50) THEN
1206     D CALL CERROR (NAME,IERR,STRING)
1207     D END IF
1208     END IF
1209     999 CONTINUE
1210     RETURN
1211     END
1212     SUBROUTINE CERROR (NAME,IERR,STRING)
1213     INTEGER IERR
1214     CHARACTER*6 NAME
1215     CHARACTER*80 STRING
1216     INTEGER COUNT
1217     SAVE COUNT
1218     DATA COUNT /0/
1219     ccc WRITE(*,1000) NAME,IERR,STRING
1220     ccc 1000 FORMAT(1X,'subroutine ',A6,', Err',I3,' comment; ',A80)
1221     COUNT = COUNT+1
1222     RETURN
1223     END
1224     C===============================================================================
1225     SUBROUTINE CCTVM00 (IERR, WXYZPV)
1226     C===============================================================================
1227     C Checks the current input specifications at the beginning of this call to
1228     C CTVMFT: (Vertex, conversion, Pointing, Mass Constraints) compound fit.
1229     C Any error detected in CTVM00 is a structural failure on the input conditions
1230     C and is (by default) treated as a fatal error. We attempt to crash the job
1231     C (after printing a specific error condition message). The studious who are
1232     C running interactively can discover how to avoid this crash; cf. the variables
1233     C "EXCUSE" and "ME", set in a local common block in CTVMFT.
1234     C If an error is detected, IERR = IJKERR(1) = 1
1235     C IJKERR(2) = the precise detected trouble.
1236     C WXYZPV is returned, it is the primary vertex double precision weight matrix
1237     C VtxVtx, the vertex "geneology", association structure is made and returned.
1238     C--Input data in the include file CTVMFT (COMMON /CTVMFC/)
1239     C NVERTX Number of vertices in this fit (MUST be at least 1)
1240     C NTRACK Number of tracks in this fit. NTRACK MUST be at least 2.
1241     C TrkVtx(MAXTRK,MAXVTX) (Logical) See the discussion in CTVMFT.
1242     C VtxPnt(MAXVTX,2) (Integer) See the discussion in CTVMFT.
1243     C TrkMcn(MAXTRK,NMASSC) (Logical) See the discussion in CTVMFT.
1244     C CMASS(NMASSC) (Real) See the discussion in CTVMFT.
1245     C TKBANK(MAXTRK) (Character*4)
1246     C Bank name (exempli gratia, 'QTRK','TRKS','SVXS','CTCS') from which
1247     C to get each track`s helix parameter and covariance data (GETTRK).
1248     C LIST (MAXTRK) (Integer)
1249     C Bank numbers of the tracks to be used.
1250     C Note that if LIST(i) is a negative integer it is assumed that the
1251     C information for this track is present unchanged from a previous call.
1252     C Edit log:
1253     C ---- ---
1254     C 11/28/94 WJA Require exactly 2 tracks for conversion vertex; always
1255     C require 1 or more tracks per vertex; If there is a "single
1256     C track vertex", this vertex must be contain at least one
1257     C multi-track exclusive vertex in its descendant chain.
1258     C 30 Jan 2003 F. Bedeschi: add checks specific to beamline constraint option
1259     C 04 FEB 2003 J. Guimaraes: Fixed bug in fiddle common block (missing chisqmx)
1260     C==============================================================================
1261     IMPLICIT NONE
1262     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
1263     #include "MitCommon/Ctvmft/interface/cctvmft.h"
1264     #include "MitCommon/Ctvmft/interface/cctvmfi.h"
1265     INTEGER IERR
1266     REAL*8 WXYZPV(3,3)
1267     INTEGER Nv,Mv,Kv, Nt,Kt, Np,Nm
1268     INTEGER I,J, II,JJ
1269     INTEGER NtrVtx(MaxVtx)
1270     REAL SUM, WORK(MAXDIM)
1271     REAL SCR
1272     CHARACTER*4 NAME
1273     CHARACTER*80 STRING
1274     REAL ZERO,MINUS,SHOUT
1275     SAVE ZERO,MINUS
1276     DATA ZERO /0.0/, MINUS /-1.0/
1277     C Local variables pertaining to zero-track vertices
1278     INTEGER NMULTI
1279     C--------------- Check Input Conditions for illegal conditions -----------------
1280     C
1281    
1282     IF ((NTRACK.LT.2 .AND. VTXPNT(1,1) .NE. -100) .OR.
1283     > (NTRACK.LT.1 .AND. VTXPNT(1,1) .EQ. -100) .OR.
1284     > NTRACK.GT.MAXTRK) THEN
1285     IJKERR(2) = 1
1286     WRITE(STRING,1001) NTRACK
1287     1001 FORMAT('Inadequate or improper number of tracks;',I2)
1288     GO TO 900
1289     END IF
1290     IF (NVERTX.LT.1 .OR. NVERTX.GT.MAXVTX) THEN
1291     IJKERR(2) = 2
1292     WRITE(STRING,1002) NVERTX
1293     1002 FORMAT('Inadequate or improper number of vertices;',I2)
1294     GO TO 900
1295     END IF
1296     IF (NMASSC.LT.0 .OR. NMASSC.GT.MAXMCN) THEN
1297     IJKERR(2) = 3
1298     WRITE(STRING,1003) NMASSC
1299     1003 FORMAT('Improper number of mass constraints;',I2)
1300     GO TO 900
1301     END IF
1302     C count the number of measured tracks
1303     DO Nv=1,MaxVtx
1304     C present at each vertex
1305     NtrVtx(Nv) = 0
1306     Do Nt=1,NTRACK
1307     IF (TrkVtx(Nt,Nv)) NtrVtx(Nv) = NtrVtx(Nv)+1
1308     END DO
1309     END DO
1310     C make the vertex geneology table
1311     DO Kv=NVERTX,1,-1
1312     DO Nv =NVERTX,1,-1
1313     VtxVtx(Kv,Nv) =.FALSE.
1314     END DO
1315     VtxVtx(Kv,Kv) = .TRUE.
1316     C Kv is a descendant of its parent,
1317     1 IF (Nv.GT.0) THEN
1318     C its parent`s parent, ...
1319     VtxVtx(Kv,Nv) = .TRUE.
1320     Nv = VtxPnt(Nv,1)
1321     GO TO 1
1322     END IF
1323     END DO
1324     C Check the logic of vertex specifications
1325     DO 10 Kv=NVERTX,1,-1
1326     IJKERR(3) = Kv
1327     C exactly 2 tracks for conversion
1328     IF (Cvtx(Kv).NE.0) THEN
1329     IF (NtrVtx(Kv).NE.2) THEN
1330     IJKERR(2) = 12
1331     WRITE (STRING,'(A,I2,A,I2,A)')
1332     & 'Conversion vertex ',Kv,' with ',NtrVtx(Kv),' tracks'
1333     GO TO 900
1334     END IF
1335     END IF
1336     C If not a beamline constrained fit -- Joao 02/09/03
1337     IF (VtxPnt(1,1) .NE. -100) THEN
1338     C a one-track vertex must have a
1339     IF (NtrVtx(Kv).EQ.1) THEN
1340     C descendant with at least 2 tracks
1341     Mv = Kv
1342     DO Nv=Kv+1,NVERTX
1343     IF (VtxPnt(Nv,1).EQ.Mv) THEN
1344     C override the vertexpointing for 1track to only 1track
1345     C IF (NtrVtx(Nv).GT.1) GO TO 5
1346     IF (NtrVtx(Nv).GT.0) GO TO 5
1347     C Craig Blocker 1/9/03 - Changed the following line from
1348     C Mv = VtxPnt(Nv,1)
1349     C to get proper test done here.
1350     Mv = Nv
1351     END IF
1352     END DO
1353     IJKERR(2) = 13
1354     WRITE(STRING,'(A,I2,A,I2,A)')
1355     & 'Vertex ',Kv,' with ',NtrVtx(Kv),
1356     & ' tracks is not legally pointed at'
1357     GO TO 900
1358     C a zero-track vertex must have 2 or more
1359     ELSE IF (NtrVtx(Kv).EQ.0) THEN
1360     C descendants with at least 2 tracks.
1361     NMULTI = 0
1362     Mv = Kv
1363     DO Nv=Kv+1,NVERTX
1364     IF (VtxPnt(Nv,1).EQ.Mv) THEN
1365     IF (NtrVtx(Nv).GT.1) NMULTI = NMULTI + 1
1366     END IF
1367     END DO
1368     C If there are only 2 vertices pointed to this one
1369     C AND they both have >1 tracks then this is a valid
1370     C zero track vertex.
1371     IF (NMULTI.GE.2) GO TO 5
1372     IJKERR(2) = 13
1373     WRITE(STRING,'(A,I2,A,I2,A)')
1374     & 'Vertex ',Kv,' with ',NtrVtx(Kv),
1375     & ' tracks is not legally pointed at'
1376    
1377     GO TO 900
1378     END IF
1379     END IF
1380     C Check that Kv`s pointing is valid
1381     5 CONTINUE
1382     Nv = VtxPnt(Kv,1)
1383     IF (Nv.LE.0) THEN
1384     IF (Nv.LT.0) VtxPnt(Kv,2) = -1
1385     ELSE
1386     C Daughter vertex number must exceed
1387     IF (Nv.GE.Kv) THEN
1388     C mother vertex number
1389     IJKERR(2) = 14
1390     WRITE (STRING,'(A,I2,A,I2)')
1391     & 'Vertex ',Kv,' has illegal target vertex number ',Nv
1392     GO TO 900
1393     END IF
1394     C conversion vertex cannot be a target
1395     IF (Cvtx(Nv).GT.0) THEN
1396     IJKERR(2) = 15
1397     WRITE (STRING,'(A,I2,A)')
1398     & 'Vertex ',Kv,' has illegal target vertex type'
1399     GO TO 900
1400     END IF
1401     C Single-track pointing if and only if to single-track vertex
1402     IF (VtxPnt(Kv,2).EQ.3.XOR.NtrVtx(Nv).EQ.1) THEN
1403     IJKERR(2) = 16
1404     WRITE (STRING,'(I2,A,I2,A)')
1405     & Kv,' ==> ',Nv,' is an illegal 1-track vertex pointing'
1406     GO TO 900
1407     END IF
1408     C zero-track pointing if and only if to zero-track vertex
1409     IF (VtxPnt(Kv,2).EQ.4.XOR.NtrVtx(Nv).EQ.0) THEN
1410     IJKERR(2) = 17
1411     WRITE (STRING,'(I2,A,I2,A)')
1412     & Kv,' ==> ',Nv,' is an illegal 0-track vertex pointing'
1413     GO TO 900
1414     END IF
1415     END IF
1416     10 CONTINUE
1417     IJKERR(3) = 0
1418     C If VtxPnt requires a primary vertex, checks that the input primary vertex
1419     C covariance matrix is "reasonable" (id est, non-singular).
1420     NP = 0
1421     DO NV=1,NVERTX
1422     IF (VtxPnt(Nv,1).EQ.0) NP = NP+1
1423     END DO
1424     IF (NP.GT.0) THEN
1425     DO I=1,3
1426     C primary vertex input position
1427     XYZPV(I) = XYZPV0(I)
1428     DO J=1,3
1429     C primary vertex error matrix
1430     WXYZPV(J,I)= EXYZPV(J,I)
1431     END DO
1432     END DO
1433     C make the primary vertex weight matrix
1434     CALL DINV(3,WXYZPV,3,WORK,I)
1435     IF (I.NE.0) THEN
1436     IJKERR(2) = 19
1437     WRITE(STRING,'(A)')
1438     & 'The input primary vertex covariance matrix is singular.'
1439     GO TO 900
1440     END IF
1441     END IF
1442     C Check the specification of tracks
1443     C every track must be at a vertex
1444     DO 20 Nt=1,NTRACK
1445     IJKERR(3) = Nt
1446     IF (LIST(Nt).LE.0) THEN
1447     IJKERR(2) = 20
1448     C some track failed TkSlct
1449     IF (LIST(Nt).LT.0) THEN
1450     IJKERR(1) = 2
1451     IERR = 2
1452     RETURN
1453     END IF
1454     WRITE(STRING,'(A,I2,A)') 'Track ',Nt,' is not specified'
1455     GO TO 900
1456     END IF
1457     IF (TKBANK(NT).EQ.'QTRK') GO TO 11
1458     IF (TKBANK(NT).EQ.'TRKS') GO TO 11
1459     IF (TKBANK(NT).EQ.'TRKV') GO TO 11
1460     IF (TKBANK(NT).EQ.'SVXS') GO TO 11
1461     IF (TKBANK(NT).EQ.'CTCS') GO TO 11
1462     IJKERR(2) = 20
1463     WRITE(STRING,1005) NT,LIST(NT),TKBANK(NT)
1464     GO TO 900
1465     1005 FORMAT('Track ',I2,',',I4,2X,A4,' is improperly specified.')
1466     11 CONTINUE
1467     II = 0
1468     DO NV=1,NVERTX
1469     IF (TrkVtx(NT,NV)) II=II+1
1470     END DO
1471     C every track belongs to a vertex
1472     IF (II.LT.1) THEN
1473     IJKERR(2) = 21
1474     WRITE (STRING,'(A,I2,A)')
1475     & 'track ',Nt,' is not at a vertex.'
1476     GO TO 900
1477     C and to only one vertex
1478     ELSE IF (II.GT.1) THEN
1479     IJKERR(2) = 22
1480     WRITE(STRING,'(A,I2,A)')
1481     & 'Track ',Nt,' appears at two vertices'
1482     GO TO 900
1483     END IF
1484     C each track may appear only once
1485     DO Kt=Nt+1,NTRACK
1486     IF (IABS(LIST(Nt)).EQ.IABS(LIST(Kt))) THEN
1487     IF (TkBank(Nt).EQ.TkBank(Kt)) THEN
1488     IJKERR(2) = 23
1489     WRITE(STRING,'(A,I2,A,I2,A)')
1490     & 'Track ',Nt,' and Track ',Kt,' are identical'
1491     GO TO 900
1492     END IF
1493     END IF
1494     END DO
1495     20 CONTINUE
1496     IJKERR(3) = 0
1497     C Check the Mass Constraint/Track/Vertex specifications
1498     DO NM=1,NMASSC
1499     II = 0
1500     SUM = 0.0
1501     DO NT=1,NTRACK
1502     IF (TrkMcn(NT,NM)) THEN
1503     II=II+1
1504     SUM = SUM + TMASS(NT)
1505     END IF
1506     END DO
1507     C check for enough tracks
1508     IF (II.LT.2) THEN
1509     IJKERR(2) = 31
1510     WRITE(STRING,1021) NM
1511     1021 FORMAT('Mass Constraint',I2,' has too few tracks.')
1512     GO TO 900
1513     END IF
1514     C check for possible mass constraint
1515     IF (CMASS(NM).LE.SUM) THEN
1516     IJKERR(2) = 32
1517     WRITE(STRING,1022) NM,CMASS(NM),SUM
1518     1022 FORMAT('Mass Constraint',I2,', mass',F6.3,' has track mass0',F6.3)
1519     GO TO 900
1520     END IF
1521     END DO
1522     C
1523     C Check for beamline constraint specifications
1524     C
1525     IF (VTXPNT(1,1) .EQ. -100) THEN
1526     SCR = 0
1527     DO I = 1,3
1528     DO J = 1,3
1529     WXYZPV(I,J) = EXYZPV(I,J)
1530     IF (I .NE. J)SCR = SCR + ABS(EXYZPV(I,J))
1531     ENDDO
1532     ENDDO
1533     IF (EXYZPV(1,1) .LE. 0.0 .OR.
1534     > EXYZPV(2,2) .LE. 0.0 .OR.
1535     > EXYZPV(3,3) .LE. 0.0) THEN
1536     IJKERR(2) = 33
1537     WRITE(STRING, 1023)EXYZPV(1,1), EXYZPV(2,2), EXYZPV(3,3)
1538     1023 FORMAT('Beamline constraint.COVARIANCE NOT SET PROPERLY. C(I,I)='
1539     > ,3(F6.3,2X))
1540     GO TO 900
1541     ENDIF
1542     IF (SCR .NE. 0.0) THEN
1543     IJKERR(2) = 34
1544     WRITE(STRING, 1024)
1545     1024 FORMAT('Beamline constraint. COVARIANCE has non diagonal terms.')
1546     GO TO 900
1547     ENDIF
1548     C Make primary vertex weight matrix
1549     CALL DINV(3,WXYZPV,3,WORK,I)
1550     IF (I .NE. 0) THEN
1551     IJKERR(2) = 35
1552     WRITE(STRING, 1025)
1553     1025 FORMAT('Beamline constraint. PV covariance cannot be inverted.')
1554     GO TO 900
1555     ENDIF
1556     IF (NVERTX .NE. 1)THEN
1557     IJKERR(2) = 36
1558     WRITE(STRING, 1026)NVERTX
1559     1026 FORMAT('Beamline constraint. NVERTX not 0: = ',F6.3)
1560     GO TO 900
1561     ENDIF
1562     ENDIF
1563     100 CONTINUE
1564     IERR = 0
1565     IJKERR(1) = 0
1566     RETURN
1567     C Executive action; Terminate with extreme prejudice.
1568     900 CONTINUE
1569     IERR = 1
1570     IJKERR(1) = 1
1571     ccc PRINT 1999, IJKERR
1572     ccc 1999 FORMAT('Improper input specification, IJKERR=',3I3)
1573     CALL CERROR ('CTVM00',IERR,STRING)
1574     C Escape hatch, for debuggery
1575     IF (EXCUSE.EQ.0) THEN
1576     SHOUT = SQRT(MINUS) / ZERO
1577     STOP
1578     ELSE
1579     RETURN
1580     END IF
1581     END
1582     C==============================================================================
1583     SUBROUTINE CCTVMFA (Nv, PRINT,IERR)
1584     C==============================================================================
1585     C
1586     C Calculates the initial approximation to the vertex position.
1587     C This subroutine tries to intersect circles that are (R,Phi) projections
1588     C of the helical trajectories of the two tracks specified in the calling
1589     C sequence.
1590     C If the circles intersect, the intersection with smaller z difference
1591     C between the 2 helices extrapolated to the intersection is chosen.
1592     C If the circles do not intersect, the vertex approximation is taken as
1593     C the point of closest appraoch of the two circles. Both cases of non-
1594     C intersection ("interiour", "exteriour") are treated.
1595     C Note that the tracks are required to travel "forwards" to the vertex,
1596     C and this requirement may override the "smallest delta Z" criterion.
1597     C Tests are made on the vertex radius and Z difference between the two
1598     C tracks, and error codes are returned for unacceptable vertices.
1599     C Note that, where possible, the calculation is completed, even if an
1600     C error condition is flagged.
1601     C Test parameter settings used to accept/reject vertex approximations;
1602     C DRMAX,DZMAX,RVMAX, TRNMAX,DSMIN
1603     C appear as data statements in the include file CTVMFT.INC.
1604     C IERR = 2 = IJKERR(1) marks failure in vertex first approximation
1605     C IJKERR(2)= 1 Concentric circles, in the first approximation
1606     C 2 (conversion) widely separated exteriour circles at the midpoint
1607     C 3 (conversion) widely separated interiour circles at the midpoint
1608     C 4 widely separated exteriour circles at the approximate vertex
1609     C 5 widely separated interiour circles at the approximate vertex
1610     C 6 Rv is too large at the chosen intersection point.
1611     C 7 delta(Z) is too large at the chosen intersection point.
1612     C 8 a track turning angle to the chosen vertex is too large
1613     C 19 no acceptable solution with an adequately positive arc length
1614     C 21 zero-track vertexing: either/both vertex momenta are too small (<0.01 MeV)
1615     C 22 zero-track vertexing: Two lines are parallel/antiparallel
1616     C Edit log:
1617     C ---- ---
1618     C 10/xx/94 WJA Allow NTRK = 1 or 2, for possible 1-track vertex; add
1619     C line-intersects-circle approximation for 1-track vertex;
1620     C add split-the-difference approximation for conversions;
1621     C detect negative JJ() values to trigger these special-case
1622     C first approximations.
1623     C 05/xx/02 MSM Allow NTRK = 0, for possible zero-track vertex; add
1624     C line-intersects-line approximation for zero-track vertex;
1625     C Detect JJ(1)=JJ(2)=0 to trigger this.
1626     C===============================================================================
1627     IMPLICIT NONE
1628     #include "MitCommon/Ctvmft/interface/cctvmco.h"
1629     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
1630     #include "MitCommon/Ctvmft/interface/cctvmft.h"
1631     #include "MitCommon/Ctvmft/interface/cctvmuv.h"
1632     INTEGER Nv, PRINT, IERR
1633     INTEGER I,J,K,L,M,N, JJ(2),II(2), NSOL, KPRINT
1634     INTEGER Nt, Mv, NTRK
1635     REAL HELIX(5,2), P(5),Q(5,5)
1636     REAL A,B, RA(2), RVI(2), TANG(2,2)
1637     REAL Xsvt,Ysvt, AA,BB,CC,DD,RR, Pt
1638     REAL TMP,PZV,FITA,FITB
1639     COMPLEX XYP0,PXYV,XYVR,PXYVR,XYTMP
1640     C Local variables for accumulating first-approximation momentum sums
1641     REAL SPh0,CPh0,SPhs,CPhs,SPhi,CPhi
1642     LOGICAL CONV
1643     REAL*8 XC(2),YC(2),RC(2)
1644     REAL*8 AB(2), XX,YY,Y0,YY2,COST,SINT,DX,DY,D,U,V
1645     INTEGER BEAM
1646     C Map the parameter order to CTVMFT form:
1647     INTEGER MAP(5)
1648     SAVE BEAM, MAP
1649     DATA BEAM /0/
1650     C (Ctg,Crv,Z0,D0,Phi)->(Crv,Phi,Ctg,D0,Z0)
1651     DATA MAP / 3,1,5,4,2 /
1652     C Variables for the first appx for zero track vertexing case
1653     C (line intersects line)
1654     C ZV="Zero-Vertex" :
1655     C First the two un-rotated vertex positions and momenta (2D)
1656     REAL ZVX1,ZVY1,ZVX2,ZVY2,ZVPX1,ZVPY1,ZVPX2,ZVPY2
1657     C Next the two rotated vertex postions and momenta (2D)
1658     REAL ZVRX1,ZVRY1,ZVRX2,ZVRY2,ZVRPX1,ZVRPY1,ZVRPX2,ZVRPY2
1659     C Next some double versions for a magnitude check (see code)
1660     REAL*8 ZVDPX1,ZVDPY1,ZVDPX2,ZVDPY2,ZVDPS1,ZVDPS2
1661     C Next some doubles for calculating sin and cos from dot and cross prod
1662     REAL*8 ZVDCS1,ZVDCS2,ZVDSN1,ZVDSN2,ZVDRSN
1663     C Next some real versions of the dot and cross products
1664     REAL ZVCS1,ZVCS2,ZVSN1,ZVSN2
1665     C Next the anticlockwise angles from right x axis to the vertex momentum
1666     REAL ZVANG1,ZVANG2
1667     C Next the rotation angle, and its sine and cosine
1668     REAL ZVROTANG,ZVSIN,ZVCOS
1669     C Next the two roated gradients (M) and intercepts (C)
1670     REAL ZVRM1,ZVRM2,ZVRC1,ZVRC2
1671     C Next some swim variables for the Z calculation
1672     REAL ZVZSWIM1,ZVZSWIM2,ZVZ1,ZVZ2,ZVPZ1,ZVPZ2
1673     C Finally the rotated point of intersection..and a temp.
1674     REAL ZVRINTX,ZVRINTY,ZVMDIFF
1675     C local variables to determine the average z of the input track set
1676     REAL SUMZOS, SUMOOS, ZAVG
1677     C Start of code
1678     C------------------------------------------------------------------------------
1679     KPRINT = 0
1680     IF (PRINT.GT.0 .AND. DBGPRT.GT.10) KPRINT=PRINT
1681     IERR = 0
1682     IJKERR(1) = 0
1683     C Special case beamline constraint -Joao 02/11/03
1684     IF (VTXPNT(1,1) .EQ.-100) THEN
1685     DO I=1,3
1686     XYZVRT(I,Nv) = XYZPV0(I)
1687     END DO
1688     GOTO 50
1689     ENDIF
1690     C Find first two tracks (if they exist)
1691     JJ(1) = 0
1692     JJ(2) = 0
1693     DO Nt=1,NTRACK
1694     IF (TrkVtx(Nt,Nv)) THEN
1695     IF (JJ(1).EQ.0) THEN
1696     JJ(1) = Nt
1697     ELSE
1698     JJ(2) = Nt
1699     GO TO 1
1700     END IF
1701     END IF
1702     END DO
1703     1 CONTINUE
1704     CONV = .FALSE.
1705     NTRK = 2
1706     C special case; conversion vertex
1707     IF (Cvtx(Nv).GT.0) CONV=.TRUE.
1708     C special case; "single track vertex"
1709     IF (JJ(2).EQ.0 .AND. JJ(1).NE.0) THEN
1710     DO Mv=Nv+1,NVERTX
1711     IF (VtxPnt(Mv,1).EQ.Nv) THEN
1712     C For 1-track vertex, JJ(2) is a vertex
1713     NTRK = 1
1714     C that points to this vertex
1715     JJ(2) = Mv
1716     END IF
1717     END DO
1718     END IF
1719     C special case: "zero track vertex"
1720     IF (JJ(2).EQ.0 .AND. JJ(1).EQ.0) THEN
1721     NTRK = 0
1722     DO Mv=Nv+1,NVERTX
1723     IF (VtxPnt(Mv,1).EQ.Nv) THEN
1724     C For 0-track vertex, JJ(2) and JJ(1) are the vertices
1725     C that point to this vertex
1726     IF (JJ(1).EQ.0) THEN
1727     JJ(1) = Mv
1728     ELSE
1729     JJ(2) = Mv
1730     END IF
1731     END IF
1732     END DO
1733     END IF
1734     C Continue if this is a zero track vertex.
1735     C Otherwise leapfrog to the right place.
1736     IF (NTRK.EQ.0) THEN
1737     C Initialise the position and momenta of 2
1738     C Vertices. This gives the 2 lines to intersect
1739     ZVX1 = XYZVRT(1,JJ(1))
1740     ZVY1 = XYZVRT(2,JJ(1))
1741     ZVX2 = XYZVRT(1,JJ(2))
1742     ZVY2 = XYZVRT(2,JJ(2))
1743     ZVPX1 = VtxP4(1,JJ(1))
1744     ZVPY1 = VtxP4(2,JJ(1))
1745     ZVPX2 = VtxP4(1,JJ(2))
1746     ZVPY2 = VtxP4(2,JJ(2))
1747     C And Z:
1748     ZVZ1 = XYZVRT(3,JJ(1))
1749     ZVZ2 = XYZVRT(3,JJ(2))
1750     ZVPZ1 = VtxP4(3,JJ(1))
1751     ZVPZ2 = VtxP4(3,JJ(2))
1752     C Initialise rotation angle to zero
1753     ZVROTANG = 0
1754     C Calculate mag**2 of each momenta
1755     ZVDPX1=ZVPX1
1756     ZVDPY2=ZVPY1
1757     ZVDPX2=ZVPX2
1758     ZVDPY2=ZVPY2
1759     ZVDPS1=ZVDPX1**2 + ZVDPY1**2
1760     ZVDPS2=ZVDPX2**2 + ZVDPY2**2
1761     C Require each mag**2>1.0E-10 which means
1762     C the mag>1.0E-5 which is 0.01 MeV which is safe.
1763     IF(ZVDPS1.LE.1.0E-10 .OR. ZVDPS2.LE.1.0E-10) THEN
1764     C One or both vertex momenta are too small!
1765     IJKERR(2) = 21
1766     GO TO 1000
1767     ENDIF
1768     C Require abs(sin(relative angle))>0.00001 (ie 1/100 millirad)
1769     C To catch parallel momenta
1770     ZVDRSN = (ZVDPX1*ZVDPY2 - ZVDPX2*ZVDPY1)
1771     & /(SQRT(ZVDPS1)*SQRT(ZVDPS2))
1772     IF(ABS(ZVDRSN).LE.1.0E-5) THEN
1773     C Vertex Momenta are too parallel
1774     IJKERR(2) = 22
1775     GO TO 1000
1776     ENDIF
1777     C Calculate Angle between each momenta and x axis:
1778     ZVDCS1 = ZVDPX1/(SQRT(ZVDPS1))
1779     ZVDCS2 = ZVDPX2/(SQRT(ZVDPS2))
1780     ZVDSN1 = ZVDPY1/(SQRT(ZVDPS1))
1781     ZVDSN2 = ZVDPY2/(SQRT(ZVDPS2))
1782     C Explicit cast to real
1783     ZVCS1 = ZVDCS1
1784     ZVCS2 = ZVDCS2
1785     ZVSN1 = ZVDSN1
1786     ZVSN2 = ZVDSN2
1787     C Pick right trig solution:
1788     C First Vertex Momentum:
1789     IF(ZVCS1.LT.0.0) THEN
1790     IF(ZVSN1.LT.0.0) THEN
1791     ZVANG1 = PI - ACOS(ZVCS1)
1792     ELSE
1793     ZVANG1 = ACOS(ZVCS1)
1794     ENDIF
1795     ELSE
1796     IF(ZVSN1.LT.0.0) THEN
1797     ZVANG1 = TWOPI - ACOS(ZVCS1)
1798     ELSE
1799     ZVANG1 = PI + ACOS(ZVCS1)
1800     ENDIF
1801     ENDIF
1802     C And second:
1803     IF(ZVCS2.LT.0.0) THEN
1804     IF(ZVSN2.LT.0.0) THEN
1805     ZVANG2 = PI - ACOS(ZVCS2)
1806     ELSE
1807     ZVANG2 = ACOS(ZVCS2)
1808     ENDIF
1809     ELSE
1810     IF(ZVSN2.LT.0.0) THEN
1811     ZVANG2 = TWOPI - ACOS(ZVCS2)
1812     ELSE
1813     ZVANG2 = PI + ACOS(ZVCS2)
1814     ENDIF
1815     ENDIF
1816     C Set rotation angle:
1817     ZVROTANG = ZVANG1 + 0.5*(ZVANG2 - ZVANG1)
1818     C Do the rotation:
1819     ZVSIN = SIN(ZVROTANG)
1820     ZVCOS = COS(ZVROTANG)
1821     ZVRX1 = ZVX1*ZVCOS - ZVY1*ZVSIN
1822     ZVRY1 = ZVX1*ZVSIN + ZVY1*ZVCOS
1823     ZVRX2 = ZVX2*ZVCOS - ZVY2*ZVSIN
1824     ZVRY2 = ZVX2*ZVSIN + ZVY2*ZVCOS
1825     ZVRPX1 = ZVPX1*ZVCOS - ZVPY1*ZVSIN
1826     ZVRPY1 = ZVPX1*ZVSIN + ZVPY1*ZVCOS
1827     ZVRPX2 = ZVPX2*ZVCOS - ZVPY2*ZVSIN
1828     ZVRPY2 = ZVPX2*ZVSIN + ZVPY2*ZVCOS
1829     C Now solve intersection in "safe" coordinates
1830     C (ie ZVRPX1 and ZVRPX2 should both be non-zero)
1831     C Calculate gradients and intercepts:
1832     ZVRM1 = ZVRPY1/ZVRPX1
1833     ZVRM2 = ZVRPY2/ZVRPX2
1834     ZVRC1 = ZVRY1 - ZVRM1*ZVRX1
1835     ZVRC2 = ZVRY2 - ZVRM2*ZVRX2
1836     C Calculate the rotated intersection:
1837     ZVRINTX = (ZVRC2-ZVRC1)/(ZVRM1-ZVRM2)
1838     ZVRINTY = (ZVRM1*ZVRINTX + ZVRC1)
1839     C Now rotate back:
1840     ZVROTANG=-1.0*ZVROTANG
1841     ZVSIN = SIN(ZVROTANG)
1842     ZVCOS = COS(ZVROTANG)
1843     XSVI(1) = ZVRINTX*ZVCOS - ZVRINTY*ZVSIN
1844     YSVI(1) = ZVRINTX*ZVSIN + ZVRINTY*ZVCOS
1845     C Now calculate how many momentum vectors to swim
1846     C to get to the right Z:
1847     C First Line:
1848     ZVZSWIM1 = (XSVI(1) - ZVX1)/ZVPX1
1849     C Second Line:
1850     ZVZSWIM2 = (XSVI(1) - ZVX2)/ZVPX2
1851     C And calculate the two z points:
1852     ZZ(1,1) = ZVZ1 + ZVZSWIM1*ZVPZ1
1853     ZZ(2,1) = ZVZ2 + ZVZSWIM2*ZVPZ2
1854     J = 1
1855     RVI(J) = SQRT(XSVI(J)**2+YSVI(J)**2)
1856     DZSVI(J) = ZZ(2,J) - ZZ(1,J)
1857     C Jump to end:
1858     GO TO 45
1859     ENDIF
1860     C loop over the two vertex-tracks
1861     DO I=1,NTRK
1862     C Track bank number
1863     J = IABS(LIST(JJ(I)))
1864     C dummy out MASS,RADIUS
1865     A = 0.0
1866     CALL CGETTRK (J,TKBANK(JJ(I)), A,A,0
1867     >, K,P,Q, IERR)
1868     C Quit, if error finding track data
1869     IF (IERR .NE. 0) THEN
1870     TKERR(JJ(I)) = IJKERR(2)
1871     GO TO 1000
1872     END IF
1873     DO K=1,5
1874     HELIX(MAP(K),I) = P(K)
1875     END DO
1876     END DO
1877     C For convenience, order the circles so that the first has smaller radius...
1878     II(1) = 1
1879     II(2) = 2
1880     IF (NTRK.EQ.2) THEN
1881     IF (ABS(HELIX(1,1)).LT.ABS(HELIX(1,2))) THEN
1882     II(1) = 2
1883     II(2) = 1
1884     END IF
1885     END IF
1886     C make the circle radii, centers
1887     DO I=1,NTRK
1888     C there are two tracks (circles)
1889     RC(I) = 0.5D0/HELIX(1,II(I))
1890     U = RC(I)+HELIX(4,II(I))
1891     XC(I) =-U*SIN(HELIX(2,II(I)))
1892     YC(I) = U*COS(HELIX(2,II(I)))
1893     RA(I) = ABS(RC(I))
1894     END DO
1895     C there are usually two intersections
1896     DO J=1,2
1897     XSVI(J) = 0.0
1898     YSVI(J) = 0.0
1899     RVI (J) = 2.0*RVMAX
1900     DZSVI(J)= 2.0*DZMAX
1901     DO I=1,2
1902     SS(I,J) = 0.0
1903     ZZ(I,J) = 0.0
1904     TANG(I,J) = PI
1905     END DO
1906     END DO
1907     IF (NTRK.GT.1) GOTO 10
1908     C Special handling of single-track vertex
1909     TMP = 1.0/(1.0+2.0*HELIX(1,1)*HELIX(4,1))
1910     C Track parametrization
1911     FITA = HELIX(1,1)*TMP
1912     FITB = HELIX(4,1)*(1+HELIX(1,1)*HELIX(4,1))*TMP
1913     XYP0 = CMPLX(COS(HELIX(2,1)),SIN(HELIX(2,1)))
1914     C Daughter vertex momentum
1915     PXYV = CMPLX(VTXP4(1,JJ(2)),VTXP4(2,JJ(2)))
1916     TMP = 1.0/ABS(PXYV)
1917     PXYV = PXYV*TMP
1918     PZV = VTXP4(3,JJ(2))*TMP
1919     C Position & momentum, rotated to PHI0=0 coordinate system
1920     XYVR = CMPLX(XYZVRT(1,JJ(2)),XYZVRT(2,JJ(2)))*CONJG(XYP0)
1921     PXYVR = PXYV*CONJG(XYP0)
1922     C Solve quadratic equation for displacement DD from vertex to track
1923     AA = FITA
1924     BB = 0.5*IMAG(PXYVR)-FITA*REAL(XYVR*CONJG(PXYVR))
1925     CC = FITA*ABS(XYVR)**2+FITB-IMAG(XYVR)
1926     TMP = BB*BB-AA*CC
1927     IF (TMP.GT.0.) THEN
1928     NSOL = 2
1929     IF (BB.LT.0.) THEN
1930     AA = -AA
1931     BB = -BB
1932     CC = -CC
1933     ENDIF
1934     BB = BB+SQRT(TMP)
1935     DD = CC/BB
1936     DO I=1,2
1937     XSVI(I) = XYZVRT(1,JJ(2))+DD*REAL(PXYV)
1938     YSVI(I) = XYZVRT(2,JJ(2))+DD*IMAG(PXYV)
1939     ZZ(2,I) = XYZVRT(3,JJ(2))+DD*PZV
1940     TANG(2,I) = 0.0
1941     DD = BB/AA
1942     ENDDO
1943     GOTO 20
1944     ENDIF
1945     C No intersection; find closest approach and use half the distance
1946     NSOL = 1
1947     C Check for line and circle antiparallel at closest approach
1948     IF (REAL(PXYVR).LT.0) THEN
1949     PXYV = -PXYV
1950     PXYVR = -PXYVR
1951     PZV = -PZV
1952     ENDIF
1953     C Use SIN(PHI)**2/(1+COS(PHI)) for (1-COS(PHI)) to reduce roundoff
1954     CC = IMAG(PXYVR)**2/(1.0+REAL(PXYVR))
1955     C Store 1/(2c) to avoid recalculation
1956     AA = 0.5/HELIX(1,1)
1957     C TMP is signed distance from circle to line, along (-SIN(PHI),COS(PHI))
1958     TMP = (IMAG(XYVR)-HELIX(4,1))*REAL(PXYVR)
1959     & -REAL(XYVR)*IMAG(PXYVR)+CC*AA
1960     XYTMP = CMPLX(IMAG(PXYV),CC)*AA
1961     & +CMPLX(0.0,HELIX(4,1))+0.5*TMP*CMPLX(-IMAG(PXYV),REAL(PXYV))
1962     DD = REAL((XYTMP-XYVR)*CONJG(PXYVR))
1963     XYTMP = XYTMP*XYP0
1964     XSVI(1) = REAL(XYTMP)
1965     YSVI(1) = IMAG(XYTMP)
1966     ZZ(2,1) = XYZVRT(3,JJ(2))+DD*PZV
1967     TANG(2,1) = 0
1968     GOTO 20
1969     C two track (or more) vertex
1970     10 CONTINUE
1971     C get the circle center separation
1972     DX = XC(2) - XC(1)
1973     DY = YC(2) - YC(1)
1974     D = DX*DX+DY*DY
1975     C the circles are concentric
1976     IF (D.LE.0.D0) THEN
1977     IJKERR(2) = 1
1978     GO TO 1000
1979     END IF
1980     D = DSQRT(D)
1981     C Separation (signed quantity); if >0, the
1982     U = D-RA(1)-RA(2)
1983     C two circles do not intersect, <0, they may
1984     FMCDIF(1) = U
1985     C Special handling of conversion vertex
1986     IF (CONV) THEN
1987     C the circles are too far appart to accept
1988     IF (ABS(U).GT.DRMAX) THEN
1989     IF (U.GT.0.0) THEN
1990     C ...exteriour
1991     IJKERR(2) = 2
1992     ELSE
1993     C ...interiour
1994     IJKERR(2) = 3
1995     END IF
1996     GO TO 1000
1997     END IF
1998     NSOL = 1
1999     C Vertex is track radius plus half of separation away from each center
2000     XSVI(1) = (XC(1)*(RA(2)+0.5*U)+XC(2)*(RA(1)+0.5*U))/D
2001     YSVI(1) = (YC(1)*(RA(2)+0.5*U)+YC(2)*(RA(1)+0.5*U))/D
2002     C Branch down to vertex acceptability checking
2003     GO TO 20
2004     END IF
2005     C Rotate, translate to a system where the
2006     COST = DX/D
2007     C two circle centers lie on the X axis.
2008     SINT = DY/D
2009     C Y` = Y1` = Y2`
2010     Y0 = (-XC(1)*YC(2)+XC(2)*YC(1))/D
2011     C X1', X2'
2012     DO I=1,2
2013     AB(I) = COST*XC(I) + SINT*YC(I)
2014     END DO
2015     U = (XC(2)+XC(1))*(XC(2)-XC(1)) + (YC(2)+YC(1))*(YC(2)-YC(1))
2016     V = (RA(2)+RA(1))*(RA(2)-RA(1))
2017     C the common circle X` (if they intersect)
2018     XX = 0.5D0 * (U-V)/D
2019     U = DSQRT((XX-AB(1))**2)
2020     C Y''**2 is positive if they intersect
2021     YY2= (RA(1)+U) * (RA(1)-U)
2022     C the circles intersect;
2023     IF (YY2.GT.0.0) THEN
2024     C two intersection points (+/- Y)
2025     YY = DSQRT(YY2)
2026     C invert the translation, rotation
2027     DO J=1,2
2028     U = YY+Y0
2029     XSVI(J) = COST*XX - SINT*U
2030     YSVI(J) = SINT*XX + COST*U
2031     YY =-YY
2032     END DO
2033     NSOL = 2
2034     GO TO 20
2035     END IF
2036     C We get here if the two circles do not intersect;
2037     C Find how close in the XY plane they approach each other,
2038     C and take the point half way between them as our vertex approximation.
2039     U = D - (RA(1)+RA(2))
2040     C A is outside of B
2041     IF (U.GT.0.0D0) THEN
2042     V = U
2043     J = 2
2044     IF (AB(1).LT.AB(2)) J=1
2045     XX = AB(J) + RA(J)
2046     C A is inside of B
2047     ELSE
2048     IF (AB(1).LT.AB(2)) THEN
2049     XX = AB(2) - RA(2)
2050     V = AB(1) - RA(1) - XX
2051     ELSE
2052     XX = AB(1) + RA(1)
2053     V = AB(2) + RA(2) - XX
2054     END IF
2055     END IF
2056     XX = XX + 0.5D0*V
2057     C rotate back to the original system
2058     XSVI(1) = COST*XX - SINT*Y0
2059     YSVI(1) = SINT*XX + COST*Y0
2060     NSOL = 1
2061     C the circles are too far appart to accept
2062     IF (V.GT.DRMAX) THEN
2063     IF (U.GT.0.0D0) THEN
2064     C ...exteriour
2065     IJKERR(2) = 4
2066     ELSE
2067     C ...interiour
2068     IJKERR(2) = 5
2069     END IF
2070     GO TO 1000
2071     END IF
2072     20 CONTINUE
2073     C loop over solutions
2074     DO 30 J=1,NSOL
2075     C loop over tracks
2076     DO I=1,NTRK
2077     C point from circle center
2078     U = (XSVI(J)-XC(I))/RC(I)
2079     C to the intersection vertex
2080     V =-(YSVI(J)-YC(I))/RC(I)
2081     C turning angle from the track origin
2082     U = ATAN2(U,V) - HELIX(2,II(I))
2083     IF (U.LT.-PI) THEN
2084     U = U + TWOPI
2085     ELSE IF (U.GT. PI) THEN
2086     U = U - TWOPI
2087     END IF
2088     TANG(I,J) = U
2089     C arc length
2090     SS(I,J) = RC(I)*U
2091     ZZ(I,J) = HELIX(5,II(I)) + SS(I,J)*HELIX(3,II(I))
2092     END DO
2093     RVI(J) = SQRT(XSVI(J)**2+YSVI(J)**2)
2094     DZSVI(J) = ZZ(2,J) - ZZ(1,J)
2095     30 CONTINUE
2096     C Check that there is at least one potentially acceptable solution!
2097     A = AMIN1(RVI(1),RVI(2))
2098     C check the vertex radius is acceptable
2099     IF (A.GT.RVMAX) THEN
2100     IJKERR(2) = 6
2101     GO TO 1000
2102     END IF
2103     A = AMIN1(ABS(DZSVI(1)),ABS(DZSVI(2)))
2104     C check the Z difference is acceptable
2105     IF (A.GT.DZMAX) THEN
2106     IJKERR(2) = 7
2107     GO TO 1000
2108     END IF
2109     A = AMAX1(ABS(TANG(1,1)),ABS(TANG(2,1)))
2110     B = AMAX1(ABS(TANG(1,2)),ABS(TANG(2,2)))
2111     C check there is an acceptable TANG
2112     IF (AMIN1(A,B).GT.TRNMAX) THEN
2113     IJKERR(2) = 8
2114     GO TO 1000
2115     END IF
2116     C minimum track arc length, sol`n 1
2117     A = AMIN1(SS(1,1),SS(2,1))
2118     C minimum track arc length, sol`n 2
2119     B = AMIN1(SS(1,2),SS(2,2))
2120     C limit the minimum arc length
2121     IF (AMAX1(A,B).LT.DSMIN) THEN
2122     IJKERR(2) = 9
2123     GO TO 1000
2124     END IF
2125     C there may be a possible acceptable solution, in (R,deltaZ,S,Tang)
2126     J = 1
2127     IF (NSOL.EQ.1) GO TO 40
2128     IF (ABS(DZSVI(2)).LT.ABS(DZSVI(1))) J=2
2129     FLIP = 0
2130     A = AMAX1(ABS(TANG(1,J)),ABS(TANG(2,J)))
2131     B = AMIN1(SS(1,J),SS(2,J))
2132     IF (RVI(J).GT.RVMAX) FLIP = 1
2133     IF (ABS(DZSVI(J)).GT.DZMAX) FLIP = FLIP+2
2134     IF (A.GT.TRNMAX) FLIP = FLIP+4
2135     IF (B.LT.DSMIN) FLIP = FLIP+8
2136     IF (FLIP.NE.0) THEN
2137     IF (J.EQ.1) THEN
2138     J = 2
2139     ELSE
2140     J = 1
2141     END IF
2142     END IF
2143     C final checks of the final solution...
2144     40 CONTINUE
2145     A = AMAX1(ABS(TANG(1,J)),ABS(TANG(2,J)))
2146     B = AMIN1(SS(1,J),SS(2,J))
2147     C check that TANG is acceptable
2148     IF (A.GT.TRNMAX) THEN
2149     IJKERR(2) = 8
2150     GO TO 1000
2151     END IF
2152     C limit the minimum arc length
2153     IF (B.LT.DSMIN) THEN
2154     IJKERR(2) = 9
2155     GO TO 1000
2156     END IF
2157     C Continue point from zero track case:
2158     45 CONTINUE
2159     C check the vertex radius
2160     IF (RVI(J).GT.RVMAX) THEN
2161     IJKERR(2) = 6
2162     GO TO 1000
2163     END IF
2164     C check the Z difference
2165     IF (ABS(DZSVI(J)).GT.DZMAX) THEN
2166     IJKERR(2) = 7
2167     GO TO 1000
2168     END IF
2169     C "acceptable" solution. Set initial vertex approximation
2170     XYZVRT(1,Nv) = XSVI(J)
2171     XYZVRT(2,Nv) = YSVI(J)
2172     XYZVRT(3,Nv) = 0.5 * (ZZ(1,J) + ZZ(2,J))
2173     C Go off and collect (GETTRK) the track data, and make the first approximation
2174     C vertex momentum sums (which will be needed for single track vertex first
2175     C approximation calculations).
2176     C GETTRK failures or failures in transporting the tracks not used in the vertex
2177     C finding to the vertex will return IERR = IJKERR(1) = 3.
2178     50 CONTINUE
2179     D IF (DBGPRT.GT.0) THEN
2180     D RR = SQRT(XYZVRT(1,Nv)**2+XYZVRT(2,Nv)**2)
2181     D WRITE (PRINT,1010) Nv,(XYZVRT(I,Nv),I=1,3),RR
2182     D1010 FORMAT (/,' Vertex',I2,
2183     D & ' Approximation; ',3F10.4,5X,'RR',F7.2)
2184     D END IF
2185     C Initialize vertex 3-momentum to the sum
2186     VtxP4(1,Nv) = 0
2187     C of daughter vertex 3-momenta
2188     VtxP4(2,Nv) = 0
2189     C (needed for 1-track vertex CTVMFA)
2190     VtxP4(3,Nv) = 0
2191     DO Mv=Nv+1,NVERTX
2192     IF (VtxPnt(Mv,1).EQ.Nv) THEN
2193     VtxP4(1,Nv) = VtxP4(1,Nv)+VtxP4(1,Mv)
2194     VtxP4(2,Nv) = VtxP4(2,Nv)+VtxP4(2,Mv)
2195     VtxP4(3,Nv) = VtxP4(3,Nv)+VtxP4(3,Mv)
2196     END IF
2197     END DO
2198     C Collect track information for this vertex
2199     SUMZOS = 0.0
2200     SUMOOS = 0.0
2201     DO Nt=1,NTRACK
2202     IF (TrkVtx(Nt,Nv)) THEN
2203     CALL CCTVM01(KPRINT,Nt,BEAM,PARERR(1,Nt),IERR)
2204     IF (IERR.NE.0) THEN
2205     C GETTRK failure, or, track cannot reach vertex
2206     GO TO 1000
2207     END IF
2208     TKERR(Nt) = 0
2209     SPh0 = SIN(Par0(2,Nt))
2210     CPh0 = COS(Par0(2,Nt))
2211     Xsvt = XYZVRT(1,Nv)*CPh0+XYZVRT(2,Nv)*SPh0
2212     Ysvt = XYZVRT(2,Nv)*CPh0-XYZVRT(1,Nv)*SPh0
2213     C Proceed blissfully
2214     SPhs = 2*Par0(1,Nt)*Xsvt
2215     C 10/23/02 Add protection here against unphysical Sphs.
2216     C Craig Blocker
2217     Sphs = max(-1.,min(1.,SPhs))
2218     CPhs = SQRT((1-SPhs)*(1+SPhs))
2219     SPhi = CPh0*Sphs+SPh0*CPhs
2220     CPhi = CPh0*CPhs-SPh0*SPhs
2221     C add this track`s contribution to vertex momentum
2222     PT = PSCALE/ABS(Par0(1,Nt))
2223     VtxP4(1,Nv) = VtxP4(1,Nv)+PT*CPhi
2224     VtxP4(2,Nv) = VtxP4(2,Nv)+PT*SPhi
2225     VtxP4(3,Nv) = VtxP4(3,Nv)+PT*Par0(3,Nt)
2226     C increment sums for average z0. Use only track with z measurement
2227     IF(PARERR(5,NT).GT.0.0.AND.VTXPNT(1,1).EQ.-100)THEN
2228     SUMZOS = SUMZOS + PAR0(5,NT)/(PARERR(5,NT)**2)
2229     SUMOOS = SUMOOS + 1.0/(PARERR(5,NT)**2)
2230     D IF (DBGPRT.GT.0) THEN
2231     D write(print,5161)NT, (par0(i,NT),i=1,5)
2232     D5161 format(1x,'track ',i3,' Par: C,phi,ctg,D,Z',5(1x,e10.4))
2233     D write(print,5162)NT, (parerr(i,NT),i=1,5)
2234     D5162 format(1x,'track ',i3,' Err: C,phi,ctg,D,Z',5(1x,e10.4))
2235     D END IF
2236     END IF
2237     END IF
2238     END DO
2239     C Get z average to get good starting point in beamline fit
2240     IF (VTXPNT(1,1).EQ.-100) THEN
2241     ZAVG = 0.0
2242     IF (SUMOOS.GT.0.0)THEN
2243     ZAVG = SUMZOS/SUMOOS
2244     XYZVRT(3,NV) = ZAVG
2245     END IF
2246     END IF
2247     1000 CONTINUE
2248     IF (IERR.NE.0) THEN
2249     IJKERR(1) = IERR
2250     ELSE IF (IJKERR(2).NE.0) THEN
2251     IERR = 2
2252     IJKERR(1) = 2
2253     IJKERR(3) = Nv
2254     END IF
2255     RETURN
2256     END
2257     C==============================================================================
2258     SUBROUTINE CCTVM01 (PRINT, NT,BEAM, PARERR, IERR)
2259     C==============================================================================
2260     C===Description:
2261     C Collects/checks track data for the use of CTVMFT for track NT (uses GETTRK),
2262     C with bank number LIST(NT), bank type TKBANK(NT), and mass TMASS(NT).
2263     C The track/vertex configuration TrkVtx and vertex approximation
2264     C XYZVRT(xyz,NV) are communicated through the include file CTVMFT.INC.
2265     C The vertex approximation is used to find the RADIUS at which dE/dX and
2266     C Coulomb multiple scattering contributions are evaluated.
2267     C===Input Arguments:
2268     C PRINT If compiled DEBUG, outputs formatted output to unit PRINT
2269     C NT Desired track, in the array LIST
2270     C BEAM Beam constraint flag, for GETTRK
2271     C===Output Arguments:
2272     C PARERR Track helix parameter errors
2273     C IERR = IJKERR(1) = 3 flags an error getting the track parameters
2274     C IJKERR(2) = 1 GETTRK returns an error for this track
2275     C 2 the track covariasnce matrix is uninvertable
2276     C 3 turns through too large an angle to the vertex
2277     C 4 moves too far backwards to the vertex
2278     C===Author:
2279     C see CTVMFT
2280     C-------------------------------------------------------------------------------
2281     IMPLICIT NONE
2282     #include "MitCommon/Ctvmft/interface/cctvmco.h"
2283     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
2284     #include "MitCommon/Ctvmft/interface/cctvmft.h"
2285     C===Local Declarations:
2286     INTEGER NT, PRINT, IERR
2287     REAL PARERR(5)
2288     LOGICAL BEAM
2289     INTEGER I,J,K,L, NV
2290     REAL P(5),Q(5,5), HELIX(5,MaxTrk),HWGT(5,5,MaxTrk)
2291     REAL RADV, TS,S
2292     REAL WORK(MAXDIM)
2293     REAL*8 RC,XYC(2),U,V, ELM(5,5)
2294     CHARACTER*80 STRING
2295     C Map the parameter order to CTVMFT form:
2296     INTEGER MAP(5)
2297     C (Ctg,Crv,Z0,D0,Phi)->(Crv,Phi,Ctg,D0,Z0)
2298     DATA MAP / 3,1,5,4,2 /
2299     C===Start of Code:
2300     C-------------------------------------------------------------------------------
2301     C get the vertex for this track
2302     DO NV=1,NVERTX
2303     IF (TrkVtx(NT,NV)) GO TO 11
2304     END DO
2305     11 RADV = SQRT(XYZVRT(1,NV)**2 + XYZVRT(2,NV)**2)
2306     C call GETTRK for track data
2307     IF (LIST(NT).GT.0) THEN
2308     CALL CGETTRK (LIST(NT),TKBANK(NT),TMASS(NT),RADV, BEAM
2309     > ,K,P,Q, IERR)
2310     C Quit on error finding track data bank
2311     IF (IERR.NE.0) THEN
2312     TKERR(NT) = IERR
2313     IJKERR(2) = 1
2314     GO TO 100
2315     END IF
2316     C save the parameter vector
2317     DO I=1,5
2318     K = MAP(I)
2319     HELIX(K,NT) = P(I)
2320     PARERR(K) = SQRT(Q(I,I))
2321     DO J=1,5
2322     L = MAP(J)
2323     ELM(L,K) = Q(J,I)
2324     END DO
2325     END DO
2326     C make -and save- the weight matrix
2327     CALL DINV(5,ELM,5,WORK,IERR)
2328     IF (IERR.NE.0) THEN
2329     TKERR(NT) = IERR
2330     IJKERR(2) = 2
2331     GO TO 100
2332     END IF
2333     DO I=1,5
2334     DO J=1,5
2335     HWGT(J,I,NT) = ELM(J,I)
2336     END DO
2337     END DO
2338     END IF
2339     C load the fit parameter vector,
2340     DO I=1,5
2341     PAR0(I,NT) = HELIX(I,NT)
2342     C and the corresponding weight matrix
2343     DO J=1,5
2344     G(J,I,NT) = HWGT(J,I,NT)
2345     END DO
2346     END DO
2347     RC = 0.5D0/HELIX(1,NT)
2348     U = RC + HELIX(4,NT)
2349     XYC(1)=-U*SIN(HELIX(2,NT))
2350     XYC(2)= U*COS(HELIX(2,NT))
2351     U = (XYZVRT(1,NV)-XYC(1))/RC
2352     V =-(XYZVRT(2,NV)-XYC(2))/RC
2353     TS = ATAN2(U,V) - HELIX(2,NT)
2354     IF (TS.LT.-PI) THEN
2355     TS = TS + TWOPI
2356     ELSE IF (TS.GT. PI) THEN
2357     TS = TS - TWOPI
2358     END IF
2359     S = RC*TS
2360     C it turns too much
2361     IF (ABS(TS).GT.TRNMAX) THEN
2362     IJKERR(2) = 3
2363     C ?what to do?
2364     ELSE IF (S.LT.DSMIN) THEN
2365     IJKERR(2) = 4
2366     END IF
2367     D IF (PRINT.GT.0) THEN
2368     D IF (IJKERR(2).NE.0) THEN
2369     D WRITE(STRING,1023) NT,LIST(NT), S
2370     D1023 FORMAT(' negative arc length, track',I2,I6 ,F7.2)
2371     D END IF
2372     D IF (PRINT.GT.0) THEN
2373     D IF (NT.EQ.1) WRITE(PRINT,1025)
2374     D WRITE(PRINT,1026) NT,(HELIX(I,NT),I=1,5), S
2375     D1025 FORMAT(/,' Track Initial helix parameters, arc length to Vtx')
2376     D1026 FORMAT(I6,2X,1P,E11.3,0P,F10.4,3F10.4, F12.2)
2377     D END IF
2378     D END IF
2379     C===Return to Caller:
2380     100 CONTINUE
2381     IF (IJKERR(2).NE.0) THEN
2382     IERR = 3
2383     IJKERR(1) = 3
2384     IJKERR(3) = NT
2385     END IF
2386     RETURN
2387     END
2388     C==============================================================================
2389     SUBROUTINE CCTVMVF (PRINT, Nv, VXI)
2390     C==============================================================================
2391     C===Description:
2392     C Calculates contributions from track Nt (at vertex Nv) to the derivative
2393     C vector VXI and derivitive matrix VMAT for the vertex fit section of CTVMFT.
2394     C This portion of the code is somewhat awkward to follow. See the derivation
2395     C of these formulae in CDF note 19zz (J.P. Marriner)
2396     C NB: this code does not properly handle tracks that turn through more than
2397     C 90 degrees between the distance of closest approach to the z axis and
2398     C the vertex. These tracks are considered pathological. The code will
2399     C be correct everywhere, however, if the proper branch of the arcsin
2400     C function is taken. (The initial approximation may be so bad that the
2401     C desired solution will not be found, however).
2402     C===Input Arguments:
2403     C Nv vertex
2404     C===Output Arguments:
2405     C VXI first derivative contributions for this track to the vertex fit
2406     C VMAT second derivative matrix (in common, include file CTVMFT.INC)
2407     C------------------------------------------------------------------------ ------
2408     C===Implicit None Declaration:
2409     IMPLICIT NONE
2410     #include "MitCommon/Ctvmft/interface/cctvmco.h"
2411     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
2412     #include "MitCommon/Ctvmft/interface/cctvmft.h"
2413     C===Local Declarations:
2414     INTEGER PRINT
2415     INTEGER NV
2416     REAL*8 VXI(MAXDIM)
2417     INTEGER I,J,K,L
2418     INTEGER NT, NtF,NvF, TI,TJ, VI,Vj
2419     REAL C,PHI,COTH, D,Z, PT
2420     REAL TWOC, S,TS,TRAD
2421     REAL SP,CP, XCYS,XSYC,XC2YS2, SINCS,COSCS,TWOCS
2422     REAL DPXDT, DPYDT, DSDC,DSDP,DSDX,DSDY
2423     REAL EMAT(3,2), FMAT(3,2)
2424     C------------------------------------------------------------------------ ------
2425     C===Start of Code:
2426     DO 50 Nt=1,NTRACK
2427     IF (.NOT.TrkVtx(Nt,Nv)) GO TO 50
2428     C current half curvature
2429     C = PAR0(1,NT) + PARDIF(1,NT)
2430     C current phi
2431     PHI = PAR0(2,NT) + PARDIF(2,NT)
2432     C current coth(theta)
2433     COTH = PAR0(3,NT) + PARDIF(3,NT)
2434     TWOC = 2.0*C
2435     C Xsv*cos(phi) + Ysv*sin(phi), -Xsv*sin(phi) + Ysv*cos(phi)
2436     C (Xsv*cos(phi))**2 + (Ysv*sin(phi))**2
2437     SP = SIN(PHI)
2438     CP = COS(PHI)
2439     XCYS = XYZVRT(1,Nv)*CP + XYZVRT(2,Nv)*SP
2440     XSYC = -XYZVRT(1,Nv)*SP + XYZVRT(2,Nv)*CP
2441     XC2YS2 = (XYZVRT(1,Nv)*CP)**2 + (XYZVRT(2,Nv)*SP)**2
2442     C t = 2.0 * c * (Xsv*cos(phi) + Ysv*sin(phi)) = argument of arcsin
2443     C s = projected distance in xy plane along helix to vertex
2444     C sin ( c*s), cos ( c*s ), 2.0 * sin(c*s) * cos(c*s)
2445     C d(arcsin(t))/dt = 1 / sqrt (1 - t**2 )
2446     TS = TWOC*XCYS
2447     C 1/20/04 Protect against TWOC begin zero. Craig Blocker
2448     if(twoc .eq. 0.) then
2449     s = xcys
2450     else
2451     S = ASIN(TS)/TWOC
2452     endif
2453     SINCS = SIN(C*S)
2454     COSCS = COS(C*S)
2455     TWOCS = 2.0*SINCS*COSCS
2456     TRAD = SQRT((1.-TS)*(1.+TS))
2457     C Helix parameters d0 and z0 are dependent variables.
2458     C They are functions of the vertex and track parameters.
2459     C 1/20/04 Protect against C being zero. Craig Blocker
2460     if(c .eq. 0.) then
2461     D = xsyc
2462     else
2463     D = XSYC - SINCS**2/C
2464     endif
2465     Z = XYZVRT(3,Nv) - COTH*S
2466     C Difference between fitted and measured d0, z0
2467     PARDIF(4,NT) = D - PAR0(4,NT)
2468     PARDIF(5,NT) = Z - PAR0(5,NT)
2469     C Remember all flavors of momentum for this track
2470     C 1/20/04 Protect against C being zero. Here it is not
2471     C clear what to set PT to. I chose 999. GeV since this is
2472     C a very large Pt in CDF, this is roughly a standard deviation
2473     C from infinite, and should be clearly recognizable. Craig Blocker
2474     if(c .eq. 0.) then
2475     PT = 999.
2476     else
2477     PT = PSCALE/ABS(C)
2478     endif
2479     C x component of momentum
2480     TrkP4(NT,1) = PT*(CP*TRAD-SP*TS)
2481     C y component of momentum
2482     TrkP4(NT,2) = PT*(SP*TRAD+CP*TS)
2483     C z component of momentum
2484     TrkP4(NT,3) = PT*COTH
2485     C Transverse momentum
2486     TrkP4(NT,5) = PT
2487     C total momentum
2488     TrkP4(NT,6) = PT*SQRT(1.0+COTH**2)
2489     C energy
2490     TrkP4(NT,4) = SQRT(TrkP4(NT,6)**2+TMASS(NT)**2)
2491     C dPx/dt
2492     DPXDT =-PT*(SP+TS*CP/TRAD)
2493     C dPy/dt
2494     DPYDT = PT*(CP-TS*SP/TRAD)
2495     C dPx/dc
2496     if(c.ne.0.) then
2497     DDA(NT,1) =-TrkP4(NT,1)/C + 2.0*XCYS*DPXDT
2498     else
2499     dda(nt,1) = 999.
2500     endif
2501     C dPx/dPhi
2502     DDA(NT,2) =-PT*(TRAD*SP+TS*CP) + TWOC*XSYC*DPXDT
2503     C dPx/dXsv
2504     DDA(NT,3) = TWOC*CP*DPXDT
2505     C dPx/dYsv
2506     DDA(NT,4) = TWOC*SP*DPXDT
2507     C dPy/dc
2508     if(c .ne. 0.) then
2509     DDA(NT,5) =-TrkP4(NT,2)/C + 2.0*XCYS*DPYDT
2510     else
2511     dda(nt,5) = 999.
2512     endif
2513     C dPy/dPhi
2514     DDA(NT,6) = PT*(TRAD*CP-TS*SP) + TWOC*XSYC*DPYDT
2515     C dPy/dXsv
2516     DDA(NT,7) = TWOC*CP*DPYDT
2517     C dPy/dYsv
2518     DDA(NT,8) = TWOC*SP*DPYDT
2519     C Get the derivatives of s with respect to the fit parameters
2520     C See if argument of arcsin is small
2521     C (track with a small turning angle to the vertex point)
2522     C Yes. use power series approximation
2523     IF (ABS(TS).LT.5.E-3) THEN
2524     DSDC =-(0.666667 - 0.3*TS**2)*TS**3
2525     C No. Use full functional form
2526     ELSE
2527     DSDC = TS/TRAD - TWOC*S
2528     ENDIF
2529     C Get full derivative ds/dc
2530     if(twoc .ne. 0.) then
2531     DSDC = DSDC/(TWOC*C)
2532     else
2533     dsdx = 999.
2534     endif
2535     C ds/dphi
2536     DSDP = XSYC/TRAD
2537     C ds/dXsv
2538     DSDX = CP/TRAD
2539     C ds/dYsv
2540     DSDY = SP/TRAD
2541     C d(d0)/dc, d(d0)/dphi, d(d0)/dcot(theta)
2542     if(c .ne. 0.) then
2543     EMAT(1,1) = -SINCS*(TWOC*S*COSCS-SINCS)/C**2 - TWOCS*DSDC
2544     else
2545     emat(1,1) = 999.
2546     endif
2547     EMAT(2,1) = -XCYS - TWOCS*DSDP
2548     EMAT(3,1) = 0.0
2549     C d(z0)/dc, d(z0)/dphi, d(z0)/dcot(theta)
2550     EMAT(1,2) = -COTH*DSDC
2551     EMAT(2,2) = -COTH*DSDP
2552     EMAT(3,2) = -S
2553     C d(d0)/dXsv, d(d0)/dYsv, d(d0)/dZsv
2554     FMAT(1,1) = -SP - TWOCS*CP/TRAD
2555     FMAT(2,1) = CP - TWOCS*SP/TRAD
2556     FMAT(3,1) = 0.0
2557     C d(z0)/dXsv, d(z0)/dYsv, d(z0)/dZsv
2558     FMAT(1,2) = -COTH*DSDX
2559     FMAT(2,2) = -COTH*DSDY
2560     FMAT(3,2) = 1.0
2561     C Index into matrix equations for track NT
2562     NtF = TOFF(NT)
2563     C Index into matrix equations for vertex NV
2564     NvF = VOFF(Nv)
2565     DO 20 I=1,3
2566     TI = NtF + I
2567     VI = NvF + I
2568     C loop over (d0,z0)
2569     DO K=1,2
2570     C Ft * G2 * Xi2
2571     VXI(Vi) = VXI(Vi) - FMAT(I,K)* (G(K+3,4,NT)*PARDIF(4,NT)
2572     & + G(K+3,5,NT)*PARDIF(5,NT))
2573     C (Gd + Et * G2 ) * Xi2
2574     VXI(Ti) = VXI(Ti) - PARDIF(K+3,NT) *
2575     & (G(I,K+3,NT) + EMAT(I,1)*G(4,K+3,NT) + EMAT(I,2)*G(5,K+3,NT))
2576     END DO
2577     DO 10 J=1,3
2578     TJ = NtF + J
2579     VJ = NvF + J
2580     C Ft * Gd * Xi3
2581     VXI(Vi) = VXI(Vi)
2582     & - (FMAT(I,1)*G(4,J,NT)+FMAT(I,2)*G(5,J,NT))*PARDIF(J,NT)
2583     C (G3 + Et * Gd) * Xi3
2584     VXI(Ti) = VXI(Ti) - (G(I,J,NT)
2585     & + EMAT(I,1)*G(4,J,NT)+EMAT(I,2)*G(5,J,NT))*PARDIF(J,NT)
2586     C G3
2587     VMAT(Ti,Tj) = G(I,J,NT)
2588     DO K=1,2
2589     C Gd * F
2590     VMAT(Vi,Tj) = VMAT(Vi,Tj)+FMAT(I,K)*G(K+3,J,NT)
2591     C Et * Gdt + Gd * E
2592     VMAT(Ti,Tj) = VMAT(Ti,Tj)
2593     & + EMAT(I,K)*G(K+3,J,NT)+ G(I,K+3,NT)*EMAT(J,K)
2594     DO L=1,2
2595     C Ft * G2 * F
2596     VMAT(Vi,Vj) = VMAT(Vi,Vj)
2597     & + FMAT(I,K)*G(K+3,L+3,NT)*FMAT(J,L)
2598     C Et * G2 * F
2599     VMAT(Vi,Tj) = VMAT(Vi,Tj)
2600     & + FMAT(I,K)*G(K+3,L+3,NT)*EMAT(J,L)
2601     C Et * G2 * E
2602     VMAT(Ti,Tj) = VMAT(Ti,Tj)
2603     & + EMAT(I,K)*G(K+3,L+3,NT)*EMAT(J,L)
2604     C end of loop on L
2605     END DO
2606     C end of loop on K
2607     END DO
2608     C end of loop on J
2609     10 CONTINUE
2610     C end of loop on I
2611     20 CONTINUE
2612     D IF (PRINT.GT.0) THEN
2613     D TS = TS/C
2614     D WRITE(PRINT,1045) NT,(PARDIF(I,NT),I=1,5), D,Z,TS
2615     D1045 FORMAT(/,' Track',I3,1X,1P,5E11.3,3X,0P,3F11.4)
2616     D WRITE(PRINT,1047) (DDA(Nt,J),J=1,8)
2617     D1047 FORMAT(10X,1P,8E11.3)
2618     D WRITE(PRINT,1046) (VXI(I),I=1,MATDIM)
2619     D DO I=1,MATDIM
2620     D WRITE(PRINT,1046) (VMAT(J,I),J=1,I)
2621     D1046 FORMAT(5X,0P,10E11.3)
2622     D END DO
2623     D END IF
2624     C end of the track loop, this vertex
2625     50 CONTINUE
2626     C------------------------------------------------------------------------ ------
2627     C===Return to Caller:
2628     C Symmetrize the derivative matrix
2629     DO I=1,MATDIM-1
2630     DO J=I+1,MATDIM
2631     VMAT(J,I) = VMAT(I,J)
2632     END DO
2633     END DO
2634     RETURN
2635     END
2636     C===============================================================================
2637     SUBROUTINE CCTVMCF (PRINT, NV, VXI)
2638     C===============================================================================
2639     C CTVMCF calculates "conversion constraint" contributions to the derivative
2640     C vector and matrix for vertex Nv (08/29/94 JPB and WJA)
2641     C--Input parameters
2642     C Input data in the include file CTVMFT (COMMON /CTVMFC/)
2643     C A physically reasonable constraint to impose in fitting a vertex at which
2644     C a photon conversion is believed to have occurred is that the invariant
2645     C mass of the two tracks be as small as possible, i.e. that the opening angle
2646     C of the two tracks at the vertex be zero. Where the tracks are copunctual,
2647     C they should be collinear.
2648     C In r-phi, a convenient way to express this constraint is that at the radius
2649     C of conversion, the sum of the azimuth and the turning angle is equal for
2650     C both tracks, i.e. Phi1+2*Crv1*S1(r) = Phi2+2*Crv2*S2(r), where S_i(r) is
2651     C the arc length (projected into r-phi) of track i at radius r, and Phi_i
2652     C and Crv_i are the azimuth and half-curvature of track i. In other words,
2653     C we equate the r-phi momentum directions of the two tracks at the vertex.
2654     C In r-z, the constraint is clearly that Ctg1 = Ctg2.
2655     C-------------------------------------------------------------------------------
2656     IMPLICIT NONE
2657     #include "MitCommon/Ctvmft/interface/cctvmco.h"
2658     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
2659     #include "MitCommon/Ctvmft/interface/cctvmft.h"
2660     INTEGER PRINT
2661     INTEGER Nv
2662     REAL*8 VXI(MaxDim)
2663     INTEGER Trk1,Trk2,NvF,NcF,I,J,IT1F,IT2F
2664     REAL XV,YV,Crv1,Crv2,Phi1,Phi2,Ctg1,Ctg2,Phs1,Phs2,S1,S2
2665     REAL DS1DX,DS2DX,DS1DY,DS2DY,DSDCrv1,DSDCrv2,DSDPhi1,DSDPhi2
2666     REAL CPhi1,CPhi2,SPhi1,SPhi2,CPhs1,CPhs2,SPhs1,SPhs2
2667     REAL SHOUT,MINUS/-1/,ZERO/0/
2668     CHARACTER*80 STRING
2669     C-------------------------------------------------------------------------------
2670     C Find the first two tracks for this vertex
2671     Trk1 = 0
2672     Trk2 = 0
2673     DO I=1,NTRACK
2674     IF (TrkVtx(I,Nv)) THEN
2675     IF (Trk1.EQ.0) THEN
2676     Trk1 = I
2677     ELSE
2678     Trk2 = I
2679     GO TO 100
2680     END IF
2681     END IF
2682     END DO
2683     100 CONTINUE
2684     C Save some possibly useful offsets into VMAT
2685     IT1F = TOFF(Trk1)
2686     IT2F = TOFF(Trk2)
2687     NvF = VOFF(Nv)
2688     NcF = COFF(Nv)
2689     C Vertex position
2690     XV = XYZVRT(1,Nv)
2691     YV = XYZVRT(2,Nv)
2692     C Track parameters
2693     Crv1 = PAR0(1,Trk1)+PARDIF(1,Trk1)
2694     Crv2 = PAR0(1,Trk2)+PARDIF(1,Trk2)
2695     Phi1 = PAR0(2,Trk1)+PARDIF(2,Trk1)
2696     Phi2 = PAR0(2,Trk2)+PARDIF(2,Trk2)
2697     Ctg1 = PAR0(3,Trk1)+PARDIF(3,Trk1)
2698     Ctg2 = PAR0(3,Trk2)+PARDIF(3,Trk2)
2699     C Simple functions of track parameters
2700     SPhi1 = SIN(Phi1)
2701     SPhi2 = SIN(Phi2)
2702     CPhi1 = COS(Phi1)
2703     CPhi2 = COS(Phi2)
2704     C Track turning angles (to get momentum direction)
2705     SPhs1 = 2*Crv1*(XV*CPhi1+YV*SPhi1)
2706     SPhs2 = 2*Crv2*(XV*CPhi2+YV*SPhi2)
2707     CPhs1 = SQRT((1+SPhs1)*(1-SPhs1))
2708     CPhs2 = SQRT((1+SPhs2)*(1-SPhs2))
2709     Phs1 = ASIN(SPhs1)
2710     Phs2 = ASIN(SPhs2)
2711     C Arc length in XY plane
2712     S1 = 0.5*Phs1/Crv1
2713     S2 = 0.5*Phs2/Crv2
2714     C d(arc length)/d(vertex position)
2715     DS1DX = CPhi1/CPhs1
2716     DS2DX = CPhi2/CPhs2
2717     DS1DY = SPhi1/CPhs1
2718     DS2DY = SPhi2/CPhs2
2719     C d(arc length)/d(track parameters)
2720     IF (ABS(CPhs1).GT.0.005) THEN
2721     DSDCrv1 = 0.5*(SPhs1/CPhs1-Phs1)/(Crv1*Crv1)
2722     ELSE
2723     DSDCrv1 = 0.33333333*SPhs1**3*(0.9*SPhs1*SPhs1-1)/(Crv1*Crv1)
2724     END IF
2725     IF (ABS(CPhs2).GT.0.005) THEN
2726     DSDCrv2 = 0.5*(SPhs2/CPhs2-Phs2)/(Crv2*Crv2)
2727     ELSE
2728     DSDCrv2 = 0.33333333*SPhs2**3*(0.9*SPhs2*SPhs2-1)/(Crv2*Crv2)
2729     END IF
2730     DSDPhi1 = (-XV*SPhi1+YV*CPhi1)/CPhs1
2731     DSDPhi2 = (-XV*SPhi2+YV*CPhi2)/CPhs2
2732     C Constraint in r-phi, C_rphi = (Phi1+2*Crv1*S1)-(Phi2+2*Crv2*S2)
2733     VXI(NcF+1) = (Phi2+Phs2)-(Phi1+Phs1)
2734     IF (VXI(NcF+1).LT.-PI) VXI(NcF+1) = VXI(NcF+1)+2D0*PI
2735     IF (VXI(NcF+1).GT.+PI) VXI(NcF+1) = VXI(NcF+1)-2D0*PI
2736     C Optional constraint in r-z, C_rz = Ctg1-Ctg2
2737     IF (Cvtx(Nv).EQ.2) THEN
2738     VXI(NcF+2) = Ctg2-Ctg1
2739     END IF
2740     C Derivatives of the r-phi constraint C_rphi with respect to the fit
2741     C parameters (X,Y,Z,Crv1,Phi1,Ctg1,Crv2,Phi2,Ctg2)
2742     C d/dXv
2743     VMAT(NVF+1,NCF+1) = 2D0*(Crv1*DS1DX-Crv2*DS2DX)
2744     C d/dYv
2745     VMAT(NVF+2,NCF+1) = 2D0*(Crv1*DS1DY-Crv2*DS2DY)
2746     C d/dCrv1
2747     VMAT(IT1F+1,NCF+1) = +(1D0+2D0*(S1+Crv1*DSDCrv1))
2748     C d/dCrv2
2749     VMAT(IT2F+1,NCF+1) = -(1D0+2D0*(S2+Crv2*DSDCrv2))
2750     C d/dPhi1
2751     VMAT(IT1F+2,NCF+1) = +(1D0+2D0*Crv1*DSDPhi1)
2752     C d/dPhi2
2753     VMAT(IT2F+2,NCF+1) = -(1D0+2D0*Crv2*DSDPhi2)
2754     C Optional derivatives of the r-z constraint C_rz with respect to
2755     C the fit parameters
2756     IF (Cvtx(Nv).EQ.2) THEN
2757     C d/dCtg1
2758     VMAT(IT1F+3,NcF+2) = +1D0
2759     C d/dCtg2
2760     VMAT(IT2F+3,NcF+2) = -1D0
2761     END IF
2762     C Symmetrize
2763     DO I=1,MATDIM-1
2764     DO J=I+1,MATDIM
2765     VMAT(J,I) = VMAT(I,J)
2766     END DO
2767     END DO
2768     C All done
2769     RETURN
2770     END
2771     C===============================================================================
2772     SUBROUTINE CCTVMPF (PRINT, NV, VXI)
2773     C===============================================================================
2774     C CTVMPD calculates "pointing constraint" contributions to the derivative
2775     C vector and matrix for vertex Nv, "pointing" at vertex Mv =VtxPnt(Nv,2)
2776     C--Input parameters
2777     C Input data in the include file CTVMFT (COMMON /CTVMFC/)
2778     C Let dX, dY, dZ = difference between the first and the second vertex
2779     C Px = VtxP4(1,Nv), etc
2780     C dX = DELV(1), etc
2781     C The first pointing constraint is Px * dY - Py * dX = 0,
2782     C The second is Pi * dZ - Pz * di = 0
2783     C (where i is x if |Px| > |Py|, otherwise i is y)
2784     C The first pointing constraint constrains the projections of the two vectors
2785     C P and d onto the x,y plane to be parallel (or antiparallel).
2786     C The second constraint constrains the vectors to be parallel or antiparallel
2787     C in 3 dimensions.
2788     C NB: The program makes this explicit choice of axes so that one can apply an
2789     C x,y pointing constraint or (optionally) a 3 dimensional constraint.
2790     C This choice of axes will not produce the desired results for the case
2791     C Px = Py = 0. This case is thought to be unlikely; It might occur for massive
2792     C objects (Z`s, eg) produced with no transverse momentum. For these types of
2793     C events one is probably better advised to use the "beam constraint" anyway.
2794     C Edit log:
2795     C ---- ---
2796     C 10/xx/94 WJA To handle 1-track vertex, add NPC variable and set it to
2797     C the number of Lagrange multipliers needed to effect the
2798     C desired pointing constraint: normally equal to VtxPnt(Nv,2)
2799     C but equal to 2 if VtxPnt(Nv,2) is zero, since 1-track point
2800     C points in both projections.
2801     C 05/xx/02 MSM Similar for zero-track vertexing.
2802     C-------------------------------------------------------------------------------
2803     IMPLICIT NONE
2804     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
2805     #include "MitCommon/Ctvmft/interface/cctvmft.h"
2806     INTEGER PRINT
2807     INTEGER Nv
2808     REAL*8 VXI(MaxDim)
2809     REAL TEMP(5), C, DELV(3)
2810     INTEGER I1,I2, IMAT,JMAT
2811     INTEGER NvF,MvF,Kv,KvF,NtF, LpF,Lp, I,J, Nt,Mv, Np
2812     INTEGER NPC
2813     C-------------------------------------------------------------------------------
2814     C IMAT points to larger PSUM component (1=x,2=y)
2815     IF (ABS(VtxP4(1,Nv)).GT.ABS(VtxP4(2,Nv))) THEN
2816     IMAT = 1
2817     JMAT = 0
2818     ELSE
2819     IMAT = 2
2820     JMAT = 4
2821     END IF
2822     C vertex towards which Nv "points"
2823     Mv = VtxPnt(Nv,1)
2824     C vertex displacement vector
2825     DO I=1,3
2826     DELV(I) = XYZVRT(I,Mv) - XYZVRT(I,Nv)
2827     END DO
2828     C offset to 2nd vertex
2829     NvF = VOFF(Nv)
2830     C offset to this pointing constraint
2831     LpF = POFF(Nv)
2832     C offset to target (primary) vertex
2833     MvF = 0
2834     C the target vertex is NOT primary
2835     IF (Mv.GT.0) MvF=VOFF(Mv)
2836     NPC = VtxPnt(Nv,2)
2837     C Use both constraints for 1-track vertex
2838     IF (NPC.EQ.3) NPC = 2
2839     IF (NPC.EQ.4) NPC = 2
2840     C Loop over pointing constraints
2841     DO 50 Np=1,NPC
2842     C offset to the current pointing constraint
2843     Lp = LpF + Np
2844     C First constraint. 1=x, 2=y
2845     IF (Np.EQ.1) THEN
2846     I1 = 1
2847     I2 = 2
2848     C otherwise 2nd constraint
2849     ELSE
2850     C 1=bigger of px,py (IMAT), 2=z
2851     I1 = IMAT
2852     I2 = 3
2853     ENDIF
2854     C "residual" (Pi)
2855     VXI(Lp) =-VtxP4(I1,Nv)*DELV(I2) +VtxP4(I2,Nv)*DELV(I1)
2856     C dPi/dI1p (1st vtx)
2857     VMAT(MvF+I1,Lp) =-VtxP4(I2,Nv)
2858     C dPi/dI2p
2859     VMAT(MvF+I2,Lp) = VtxP4(I1,Nv)
2860     C dPi/dI1s (2nd vtx)
2861     VMAT(NvF+I1,Lp) =-VMAT(MvF+I1,Lp)
2862     C dPi/dI2s
2863     VMAT(NvF+I2,Lp) =-VMAT(MvF+I2,Lp)
2864     D IF (PRINT.GT.0) THEN
2865     D WRITE(PRINT,2040) Lp, Nv,Mv, I1,I2, VXI(Lp)
2866     D @, VMAT(MVF+I1,Lp),VMAT(MvF+I2,Lp),VMAT(NvF+I1,Lp),VMAT(NvF+I2,Lp)
2867     D2040 FORMAT(/,' Pnt Lp',I3, 2X,2I2,I4,I3, 1P,E11.3,3X,4E11.3)
2868     D END IF
2869     C Scan over ancestor vertices
2870     DO 40 Kv=NVERTX,Nv,-1
2871     IF (.NOT.VtxVtx(Kv,Nv)) THEN
2872     GO TO 40
2873     END IF
2874     KvF = VOFF(Kv)
2875     C Loop over tracks
2876     DO 20 Nt=1,NTRACK
2877     C check vertex association
2878     IF (.NOT.TrkVtx(Nt,Kv)) GO TO 20
2879     C offset for track Nt
2880     NtF = TOFF(Nt)
2881     IF (Np .EQ. 1) THEN
2882     C (R,Phi) pointing constraint, dP1/dc, dP1/dphi, dP1/dcotg, dP1/dXsv, dP1/dYsv
2883     TEMP(1) = DDA(Nt,1)*DELV(2) - DDA(Nt,5)*DELV(1)
2884     TEMP(2) = DDA(Nt,2)*DELV(2) - DDA(Nt,6)*DELV(1)
2885     TEMP(3) = 0.0
2886     TEMP(4) = DDA(Nt,3)*DELV(2) - DDA(Nt,7)*DELV(1)
2887     TEMP(5) = DDA(Nt,4)*DELV(2) - DDA(Nt,8)*DELV(1)
2888     ELSE
2889     C (R,Z) pointing constraint, dP2/dc, dP2/dphi, dP2/dcotg, dP2/dXsv, dP2/dYsv
2890     C = PAR0(1,Nt) + PARDIF(1,Nt)
2891     TEMP(1) = DDA(Nt,JMAT+1)*DELV(3)
2892     TEMP(1) = TEMP(1) + TrkP4(Nt,3)*DELV(IMAT)/C
2893     TEMP(2) = DDA(Nt,JMAT+2)*DELV(3)
2894     TEMP(3) =-DELV(IMAT)*TrkP4(Nt,5)
2895     TEMP(4) = DDA(Nt,JMAT+3)*DELV(3)
2896     TEMP(5) = DDA(Nt,JMAT+4)*DELV(3)
2897     END IF
2898     VMAT(NtF+1,Lp) = TEMP(1)
2899     VMAT(NtF+2,Lp) = TEMP(2)
2900     VMAT(NtF+3,Lp) = TEMP(3)
2901     VMAT(KvF+1,Lp) = TEMP(4) + VMAT(KvF+1,Lp)
2902     VMAT(KvF+2,Lp) = TEMP(5) + VMAT(KvF+2,Lp)
2903     D IF (PRINT.GT.0) THEN
2904     D WRITE(PRINT,2041) NT,LP, TEMP
2905     D2041 FORMAT(7X,I3,I5,22X,7E11.3)
2906     D END IF
2907     C End track loop
2908     20 CONTINUE
2909     C End ancestor vertex loop
2910     40 CONTINUE
2911     C End pointing constraints loop
2912     50 CONTINUE
2913     C===Return to Caller:
2914     100 CONTINUE
2915     C Symmetrize the derivative matrix
2916     DO I=1,MATDIM-1
2917     DO J=I+1,MATDIM
2918     VMAT(J,I) = VMAT(I,J)
2919     END DO
2920     END DO
2921     RETURN
2922     END
2923     C===============================================================================
2924     SUBROUTINE CCTVMMF (PRINT, NM, VXI)
2925     C===============================================================================
2926     C Derivative contributions for the CTVM mass constraint fitting
2927     C--Input parameter
2928     C Nm The mass constraint index
2929     C-------------------------------------------------------------------------------
2930     IMPLICIT NONE
2931     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
2932     #include "MitCommon/Ctvmft/interface/cctvmft.h"
2933     INTEGER PRINT
2934     INTEGER NM
2935     REAL*8 VXI(MAXDIM)
2936     REAL*8 SUM
2937     INTEGER I,J, Nt,Nv, LmF,NvF,NtF
2938     REAL C
2939     C-------------------------------------------------------------------------------
2940     LmF = MOFF + Nm
2941     C Difference in m**2 of tracks and constraint / 2
2942     SUM = SQRT(McnP4(1,Nm)**2 + McnP4(2,Nm)**2 + McnP4(3,Nm)**2)
2943     SUM = (McnP4(4,Nm) + SUM) * (McnP4(4,Nm) - SUM)
2944     SUM = DSQRT(SUM)
2945     VXI(LmF) = 0.5D0 * (CMASS(Nm)+SUM) * (CMASS(Nm)-SUM)
2946     C Loop over tracks contributing to this mass constraint
2947     DO 50 Nv=1,NVERTX
2948     NvF = VOFF(Nv)
2949     DO 40 NT=1,NTRACK
2950     IF (.NOT.TrkVtx(Nt,Nv)) GO TO 40
2951     IF (.NOT.TrkMcn(Nt,Nm)) GO TO 40
2952     C Index into matrix equations for track NT
2953     NtF = TOFF(Nt)
2954     C dM**2/dc, dM**2/dphi, dM**2/dcot(theta)
2955     C = PAR0(1,Nt) + PARDIF(1,Nt)
2956     SUM = -McnP4(4,Nm)*TrkP4(Nt,6)**2/TrkP4(Nt,4)
2957     SUM = (SUM + McnP4(3,Nm)*TrkP4(Nt,3)) / C
2958     SUM = SUM - McnP4(1,Nm)*DDA(Nt,1) - McnP4(2,Nm)*DDA(Nt,5)
2959     VMAT(NtF+1,LmF) = SUM
2960     SUM =-McnP4(1,Nm)*DDA(Nt,2) - McnP4(2,Nm)*DDA(Nt,6)
2961     VMAT(NtF+2,LmF) = SUM
2962     SUM = (McnP4(4,Nm)*TrkP4(Nt,3) / TrkP4(Nt,4)-McnP4(3,Nm))
2963     SUM = TrkP4(Nt,5) * SUM
2964     VMAT(NtF+3,LmF) = SUM
2965     C dM**2/dXsv, dM**2/dYsv
2966     VMAT(NvF+1,LmF) = VMAT(NvF+1,LmF)
2967     & - McnP4(1,Nm)*DDA(Nt,3)-McnP4(2,Nm)*DDA(Nt,7)
2968     VMAT(NvF+2,LmF) = VMAT(NvF+2,LmF)
2969     & - McnP4(1,Nm)*DDA(Nt,4)-McnP4(2,Nm)*DDA(Nt,8)
2970     D IF (PRINT.GT.0) THEN
2971     D WRITE(PRINT,1045) NT, VXI(LmF)
2972     D @, (VMAT(NvF+J,LmF),J=1,2),(VMAT(NtF+J,LmF),J=1,3)
2973     D1045 FORMAT(/,' Mcn, Tk',I3, 1P,E11.3,2X,5E11.3)
2974     D END IF
2975     40 CONTINUE
2976     C Continue loop on tracks
2977     50 CONTINUE
2978     C-------------------------------------------------------------------------------
2979     C===Return to Caller:
2980     C Symmetrize the derivative matrix
2981     DO I=1,MATDIM-1
2982     DO J=I+1,MATDIM
2983     VMAT(J,I) = VMAT(I,J)
2984     END DO
2985     END DO
2986     RETURN
2987     END
2988     C===============================================================================
2989     SUBROUTINE CCTVMPR(LSUNIT,DBGPRT,PARERR)
2990     C===============================================================================
2991     C Author: John Marriner, CDF, FNAL (with a little help from his friends)
2992     C print the fit results of CTVMFT
2993     C Input parameters
2994     C LSUNIT = fortran logical unit for write
2995     C DBGPRT = print level
2996     C PARERR Original (input) track parameters
2997     C Preconditions
2998     C CTVMFT must have been called and returned no error
2999     C CTVMPR assumes fit information is stored in common defined by CTVMFT.INC
3000     C-------------------------------------------------------------------------------
3001     IMPLICIT NONE
3002     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
3003     #include "MitCommon/Ctvmft/interface/cctvmft.h"
3004     INTEGER DBGPRT, LSUNIT
3005     REAL PARERR(5,MaxTrk)
3006     INTEGER I,J,K,L,M,N, IFAIL, IM, IN, INDEX(5)
3007     INTEGER Nt,Nv,Mv, Nc,Np,Nm, NtF,NvF, NPAR, NVPAR, NPC
3008     INTEGER NtrVtx(0:Maxvtx), TMcn(MaxTrk)
3009     LOGICAL PRIMARY
3010     REAL CHIP, VALUE,SIGMA, U,V,W, ERRRAT(5), PULL(3)
3011     REAL DXYZ(3), Dr,Dz, Dl(3)
3012     REAL ERR(MAXDIM), WORK(MAXDIM), CORR(MAXDIM,MAXDIM)
3013     REAL*8 P4(4), EPAR(5,5)
3014     INTEGER MRUN,MNEV
3015     INTEGER MTRACK(MaxTrk)
3016     LOGICAL FIRST
3017     CHARACTER*9 VN, VP, VS, VB
3018     SAVE MRUN,MNEV, VP,VS,VB
3019     DATA VP / 'primary ' /, VS / 'secondary' /, VB / ' ' /
3020     DATA MRUN /-1/, MNEV /-1/
3021     C-------------------------------------------------------------------------------
3022     C Write header, chi-squared, # deg of freedom
3023     IF (RunNum.NE.MRUN .OR. TrgNum.NE.MNEV) THEN
3024     WRITE(LSUNIT,1000)
3025     1000 FORMAT('1',123('=') )
3026     MRUN = RunNum
3027     MNEV = TrgNum
3028     END IF
3029     DO I=1,MaxTrk
3030     MTRACK(I) = I
3031     END DO
3032     Nc = 0
3033     Np = 0
3034     PRIMARY =.FALSE.
3035     NtrVtx(0) = 0
3036     DO Nv=1,NVERTX
3037     NtrVtx(Nv) = 0
3038     Do Nt=1,NTRACK
3039     IF (TrkVtx(Nt,Nv)) NtrVtx(Nv) = NtrVtx(Nv)+1
3040     END DO
3041     IF (VtxPnt(Nv,1).EQ.0) PRIMARY =.TRUE.
3042     Nc = Nc + Cvtx(Nv)
3043     IF (VtxPnt(Nv,1).GE.0) THEN
3044     NPC = VtxPnt(Nv,2)
3045     IF (NPC.EQ.3) NPC = 2
3046     IF (NPC.EQ.4) NPC = 2
3047     Np = Np+NPC
3048     END IF
3049     END DO
3050     C make the fit errors and the correlation matrix
3051     NPAR = TOFF(NTRACK)+3
3052     C Loop over fitted parameters
3053     DO I=1,NPAR
3054     C Get error = sqrt(diagonal element)
3055     ERR(I) = DSQRT(VMAT(I,I))
3056     END DO
3057     C Correlation matrix
3058     DO I=1,NPAR
3059     DO J=1,NPAR
3060     CORR(I,J) = VMAT(I,J)/(ERR(I)*ERR(J))
3061     END DO
3062     END DO
3063     I = RunNum
3064     J = TrgNum
3065     CHIP = AMIN1(CHISQR(0),999.0)
3066     CALL CMCALC(NTRACK,MTRACK, Value,SIGMA, P4)
3067     VALUE = AMIN1(VALUE,999.999)
3068     SIGMA = AMIN1(SIGMA, 99.999)
3069     WRITE(LSUNIT,1001) I,J,CHIP,NDOF,ITER,NTSCUT
3070     &, NTRACK,NVERTX,Np,Nc,NMASSC,Value,SIGMA
3071     1001 FORMAT
3072     &(1X,123('-'), /,' Event ',I5,'.',I6,'; Ct_VM fit results'
3073     &, 5X,'Chi square =',F7.2,' Ndof',I3,' (Iter',I3,', NtCut',I3,')'
3074     &, 20X,'Mass Sigma'
3075     &, /, 18X,I2,' Tracks,',I2,' Vertices; Constraints (Pointing',I3
3076     &, ', Conversion',I2,', Mass',I2,')',16X,F8.3,F7.3
3077     & )
3078     C write vertex fit Chi-Square results
3079     WRITE(LSUNIT,1010)
3080     1010 FORMAT(' Vertex coordinate fit results' ,/
3081     &, 11X,'Vtx Ntr',5X,'Xv',7X,'Yv',8X,'Zv',7X,'Chisq'
3082     &, 3X,'Np Nc DLr Dlz'
3083     &, 12X,'SumPx SumPy SumPz Sum_E')
3084     L = 1
3085     IF (PRIMARY) L=0
3086     DO Nv=L,NVERTX
3087     IF (Nv.GT.0) THEN
3088     NvF = VOFF(Nv)
3089     END IF
3090     CHIP = AMIN1(CHIV(Nv),999.0)
3091     Dr = 0
3092     Dz = 0
3093     IF (Nv.EQ.0) THEN
3094     NvF = 0
3095     Np =-1
3096     Nc =-1
3097     WRITE(LSUNIT,1015) VP,Nv,NtrVtx(Nv),(XYZVRT(I,Nv),I=1,3),CHIP
3098     WRITE(LSUNIT,1016) (ERR(NvF+I),I=1,3)
3099     ELSE
3100     VN = VS
3101     IF (Nv.GT.1) VN=VB
3102     Mv = VtxPnt(Nv,1)
3103     Nc = Cvtx(Nv)
3104     Np = VtxPnt(Nv,2)
3105     IF (Np.LT.0) Np = 0
3106     IF (NP.EQ.3) NP = 2
3107     IF (NP.EQ.4) NP = 2
3108     IF (Np.LT.1) PCON(Nv,1)=0.0
3109     IF (Np.LT.2) PCON(Nv,2)=0.0
3110     NvF = VOFF(Nv)
3111     IF (Np.LE.0) THEN
3112     WRITE(LSUNIT,1015) VN,Nv,NtrVtx(Nv),(XYZVRT(I,Nv),I=1,3)
3113     &, CHIP,Np,Nc, (VtxP4(I,Nv),I=1,4)
3114     WRITE(LSUNIT,1016) (ERR(NvF+I),I=1,3)
3115     ELSE
3116     CALL CDCALC(Nv,Mv,DXYZ,Dr,Dz,Dl)
3117     WRITE(LSUNIT,1017) VN,Nv,Mv,NtrVtx(Nv),(XYZVRT(I,Nv),I=1,3)
3118     &, CHIP,Np,Nc,Dr,Dz,(VtxP4(I,Nv),I=1,4)
3119     WRITE(LSUNIT,1018) (ERR(NvF+I),I=1,3),Dl
3120     END IF
3121     END IF
3122     1015 FORMAT(1X,A9,I3,I5, F11.4,F9.4,F10.4,F9.2
3123     &, I5,I4,20X ,F14.3,3F8.3)
3124     1016 FORMAT(20X,2F9.4,F10.4 , 58X,3F6.3)
3125     1017 FORMAT(1X,A9,I3,',',I1,I3,2X, F9.4,F9.4,F10.4,F9.2
3126     &, I5,I4,F9.4,F10.4,5X,F10.3,3F8.3)
3127     1018 FORMAT(20X,2F9.4,F10.4,15X,2F7.4,F8.4, 20X,3F6.3)
3128     END DO
3129     WRITE(LSUNIT,*)
3130     C Write information on mass constraints
3131     IF (NMASSC.GT.0) THEN
3132     DO Nm=1,NMASSC
3133     L = 0
3134     DO Nt=1,NTRACK
3135     IF (TrkMcn(Nt,Nm)) THEN
3136     L = L+1
3137     TMcn(L) = Nt
3138     END IF
3139     END DO
3140     IF (Nm.EQ.1) THEN
3141     WRITE(LSUNIT,1020) Nm, CMASS(Nm),FMCDIF(Nm),(TMcn(I),I=1,L)
3142     1020 FORMAT(' Mass Constraints; Mcn',I2,' Mass ',F7.4,' Gev/c**2'
3143     &, ' Residual ' ,1P,E9.1,' Mev/c**2 Tracks',10I3)
3144     ELSE
3145     WRITE(LSUNIT,1021) Nm, CMASS(Nm),FMCDIF(Nm),(TMcn(I),I=1,L)
3146     1021 FORMAT(I24, F13.4,17X,1P,E12.1 ,18X ,10I3)
3147     END IF
3148     END DO
3149     WRITE(LSUNIT,*)
3150     END IF
3151     C Now, print the track fit results
3152     WRITE(LSUNIT,1050)
3153     1050 FORMAT(' Track parameter fit results -'
3154     &,/,5X,'Vtx Bank Mass Crv',10X,'Phi',7X,'Ctg',8X,'D0'
3155     &, 7X,'Z0',8X,'Chisq',22X,'ErrFit / ErrMst')
3156     DO 50 Nv=1,Nvertx
3157     WRITE(LSUNIT,*)
3158     DO 49 Nt=1,Ntrack
3159     IF (.NOT.TrkVtx(Nt,Nv)) GO TO 49
3160     NtF = TOFF(Nt)
3161     VALUE = AMIN1(CHIT(Nt),999.0)
3162     DO I=1,3
3163     ERRRAT(I) = ERR(NtF+I) / PARERR(I,Nt)
3164     END DO
3165     WRITE(LSUNIT,1055) Nt,Nv, TKBANK(Nt),LIST(Nt),TMASS(Nt)
3166     &, (PAR(J,Nt),J=1,5), VALUE
3167     WRITE(LSUNIT,1056) (ERR(NtF+J),J=1,3), (ERRRAT(J),J=1,3)
3168     1055 FORMAT(I3,')',I3,3X,A4,I3,F8.4,1P,E12.3,0P,2F10.5,2F10.4,F9.2)
3169     1056 FORMAT(25X,1P,E12.3,0P,2F10.5, 49X, 3F6.3)
3170     IF (DBGPRT.LT.987654) GO TO 49
3171     C Loop over weight matrix
3172     DO I = 1, 5
3173     DO J = 1, 5
3174     EPAR(I,J) = G(I,J,NT)
3175     END DO
3176     END DO
3177     C Invert weight matrix to get error matrix
3178     CALL DINV(5,EPAR,5,WORK,IFAIL)
3179     C Get index into fit error matrix for track NT
3180     C Loop over fitted parameters (first 3 in a track)
3181     DO I = 1, 3
3182     C Get sigma = denominator for pull
3183     SIGMA = EPAR(I,I) - VMAT(NtF+I,NtF+I)
3184     C Allow modest underflow (rounding errors?)
3185     IF (ABS(SIGMA) .LT. 0.001D0*EPAR(I,I)) SIGMA = 0.001D0*EPAR(I,I)
3186     C Test for negative argument
3187     IF (SIGMA .LT. 0.0) GO TO 45
3188     C Pull = (Fitted value - CTC fit)/sigma
3189     PULL(I) = PARDIF(I,NT)/SQRT(SIGMA)
3190     C Continue loop on fitted parameters
3191     END DO
3192     C Write pulls, contribution to chi-squared for this track
3193     WRITE (LSUNIT,1062) (PULL(I),I=1,3)
3194     1062 FORMAT(6X,' Pulls',0P,3F9.4)
3195     GO TO 49
3196     45 CONTINUE
3197     WRITE (LSUNIT,21)
3198     21 FORMAT (3X,' Pulls. Error in calculating pulls.',
3199     & ' Fit is suspect.')
3200     C Continue loop on tracks
3201     49 CONTINUE
3202     50 CONTINUE
3203     C Loop over fitted parameters
3204     60 CONTINUE
3205     IF (DBGPRT.LE.99) GO TO 900
3206     C Write header for error matrix print
3207     WRITE (LSUNIT,1060)
3208     1060 FORMAT(/,' Correlation matrix')
3209     DO I=1,NPAR
3210     WRITE(LSUNIT,1065) (CORR(I,J),J=1,I)
3211     1065 FORMAT( 8(1X,3F5.2) )
3212     IF (MOD(I,3).EQ.0) WRITE(LSUNIT,*)
3213     END DO
3214     C Done. Exit
3215     900 CONTINUE
3216     RETURN
3217     END
3218     C===============================================================================
3219     SUBROUTINE CCTVMsv (WHICH, WHERE)
3220     C===============================================================================
3221     C Silly, trivial little routine to save, interchange, or restore the results
3222     C of a CTVMFT fit.
3223     C WHICH < 0 Copy the CTVMFT fit results to local storage for preservation
3224     C = 0 Interchange the stored fit result with that in the CTVMFT common
3225     C > 0 Overwrite the CTVMFT fit result with the stored result
3226     C WHERE An index specifying where to store or where to extract fit
3227     C information.
3228     C-------------------------------------------------------------------------------
3229     IMPLICIT NONE
3230     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
3231     #include "MitCommon/Ctvmft/interface/cctvmft.h"
3232     INTEGER IJKLMN
3233     PARAMETER(IJKLMN = MAXDIM*(MAXDIM+1))
3234     INTEGER WHICH, WHERE
3235     INTEGER I
3236     INTEGER SAVRSL(UDIM,4), SLUSH(UDIM)
3237     REAL*8 UMAT (MAXDIM*(MAXDIM+1),4)
3238     REAL*8 BLUSH(MAXDIM*(MAXDIM+1))
3239     REAL SCREAM, MINUS, ZERO
3240     SAVE SAVRSL, UMAT, MINUS,ZERO
3241     DATA MINUS /-1.0/, ZERO /0.0/
3242     C============ save or restore existing constrained fit results ===============
3243     IF (WHERE.LE.0 .OR. WHERE.GT.4) THEN
3244     PRINT 1000, WHERE
3245     1000 FORMAT (' CTVMsave; nonsense WHERE!' )
3246     SCREAM = SQRT(MINUS) / ZERO
3247     STOP
3248     END IF
3249     IF (WHICH) 10,20,30
3250     C save the existing fit from CTVMFq,r
3251     10 CONTINUE
3252     DO I=1,UDIM
3253     SAVRSL(I,WHERE) = UVWXYZ(I)
3254     END DO
3255     DO I=1,IJKLMN
3256     UMAT(I,WHERE) = VMAT(I,1)
3257     END DO
3258     GO TO 100
3259     C flip the stored fit with that in CTVMFq,r
3260     20 CONTINUE
3261     DO I=1,UDIM
3262     SLUSH (I) = SAVRSL(I,WHERE)
3263     SAVRSL(I,WHERE) = UVWXYZ(I)
3264     UVWXYZ(I) = SLUSH (I)
3265     END DO
3266     DO I=1,IJKLMN
3267     BLUSH(I) = UMAT(I,WHERE)
3268     UMAT (I,WHERE) = VMAT(I,1)
3269     VMAT(I,1) = BLUSH(I)
3270     END DO
3271     GO TO 100
3272     C restore the CTVMFq,r contents
3273     30 CONTINUE
3274     DO I=1,UDIM
3275     UVWXYZ(I) = SAVRSL(I,WHERE)
3276     END DO
3277     DO I=1,IJKLMN
3278     VMAT(I,1) = UMAT(I,WHERE)
3279     END DO
3280     100 CONTINUE
3281     RETURN
3282     END
3283     C======================================================================= =======
3284     SUBROUTINE CMCALC (NTRKQ,MTRACK, FMASS,DMASS, P4)
3285     C======================================================================= =======
3286     C
3287     C=======Description
3288     C
3289     C Input parameters:
3290     C Requires the common in the CTVMFT include file to have relevant information
3291     C stored from a CTVMFT entrance.
3292     C NTRKQ = Number of tracks comprising the invariant mass.
3293     C MTRACK(i) selects the track specified in LIST(i) in the CTVMFT call
3294     C Output parameters:
3295     C FMASS = invariant mass of track combination
3296     C DMASS = computed error on the mass (will be returned as negative if
3297     C DMASS**2 was computed to be negative. This should not happen
3298     C if the matrix VMAT is valid)
3299     C=======Author
3300     C John Marriner
3301     C 6 April 1992
3302     C----------------------------------------------------------------------- -------
3303     IMPLICIT NONE
3304     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
3305     #include "MitCommon/Ctvmft/interface/cctvmft.h"
3306     INTEGER NTRKQ
3307     INTEGER MTRACK(MAXTRK)
3308     REAL FMASS, DMASS
3309     INTEGER I,J, IERR, Nv,NvF, Nt,NtF, NDIM, Nvx,NVRTX(MaxVtx)
3310     REAL DMASSQ
3311     REAL*8 SUM,QMASS, P4(4), DM(MAXDIM)
3312     CHARACTER*80 STRING
3313     CHARACTER*6 NAME
3314     DATA NAME /'MCALC '/
3315     C===============================================================================
3316     CALL VZERO(P4,2*4)
3317     CALL VZERO(DM,2*MAXDIM)
3318     FMASS = 0.0
3319     DMASS = 0.0
3320     C complain
3321     IF (NTRKQ.GT.MAXTRK) THEN
3322     IERR = 91
3323     WRITE(STRING,901) NAME,IERR,NTRKQ
3324     901 FORMAT(A6,I3,'; ',I2,' is too many tracks')
3325     CALL CERROR('MCALC ',IERR,STRING)
3326     FMASS =-1.0
3327     GO TO 100
3328     END IF
3329     DO J=1,NTRKQ
3330     Nt = MTRACK(J)
3331     C energy
3332     TrkP4(NT,4) = SQRT(TrkP4(NT,6)**2+TMASS(NT)**2)
3333     DO I=1,4
3334     P4(I) = P4(I) + TrkP4(Nt,I)
3335     END DO
3336     END DO
3337     NDIM = 0
3338     Nvx = 0
3339     CALL VZERO(NVRTX,MAXVTX)
3340     DMASSQ = 0.0
3341     C Loop over tracks in the fit, find dM
3342     DO 10 J=1,NTRKQ
3343     Nt = MTRACK(J)
3344     NtF = TOFF(Nt)
3345     C find the vertex for this track
3346     Nv = 1
3347     DMASSQ = DMASSQ + TMASS(Nt)
3348     DO WHILE (.NOT.TrkVtx(Nt,Nv))
3349     Nv = Nv+1
3350     END DO
3351     C count number of vertices involved
3352     IF (NVRTX(Nv).EQ.0) THEN
3353     Nvx = Nvx+1
3354     NVRTX(Nv) = Nv
3355     END IF
3356     NvF = VOFF(Nv)
3357     C maximum matrix dimension in VMAT
3358     NDIM = MAX0(NDIM,NtF+3)
3359     C first,dM**2/dXsv and dM**2/dYsv, treat the displacement to this vertex
3360     DM(NvF+1) = DM(NvF+1)-2.0*(P4(1)*DDA(Nt,3)+P4(2)*DDA(Nt,7))
3361     DM(NvF+2) = DM(NvF+2)-2.0*(P4(1)*DDA(Nt,4)+P4(2)*DDA(Nt,8))
3362     C then, dM**2/dc, dM**2/dphi, dM**2/dcot(theta), helix parameters for this track
3363     SUM = -P4(4)*TrkP4(Nt,6)**2/TrkP4(Nt,4) + P4(3)*TrkP4(Nt,3)
3364     SUM = SUM/PAR(1,Nt) - (P4(1)*DDA(Nt,1) + P4(2)*DDA(Nt,5))
3365     DM(NtF+1) = 2.0*SUM
3366     DM(NtF+2) =-2.0*(P4(1)*DDA(Nt,2) + P4(2)*DDA(Nt,6))
3367     SUM = (P4(4)*TrkP4(Nt,3)/TrkP4(Nt,4) - P4(3)) * TrkP4(Nt,5)
3368     DM(NtF+3) = 2.0*SUM
3369     10 CONTINUE
3370     C mass, mass**2
3371     QMASS = DSQRT(P4(1)**2+P4(2)**2+P4(3)**2)
3372     IF (P4(4).LE.QMASS) THEN
3373     IF (Nvx.EQ.1 .AND. Cvtx(Nv).GT.0) THEN
3374     QMASS = DMASSQ
3375     ELSE
3376     C ? crunch
3377     C 10/23/02 Change next line by adding minus signs so that code
3378     C does not bomb is energy is less than momentum due to roundoff error.
3379     C Craig Blocker
3380     QMASS = -DSQRT(-(P4(4)+QMASS)*(P4(4)-QMASS))
3381     END IF
3382     ELSE
3383     QMASS = DSQRT((P4(4)+QMASS)*(P4(4)-QMASS))
3384     END IF
3385     FMASS = QMASS
3386     C Set error in mass squared = 0 for summing
3387     DMASSQ = 0.0
3388     DO I=1,NDIM
3389     DO J=1,NDIM
3390     DMASSQ = DMASSQ + DM(I)*VMAT(J,I)*DM(J)
3391     END DO
3392     END DO
3393     C check for, and flag, negative error**2
3394     IF (DMASSQ.GE.0.) THEN
3395     DMASS = SQRT(DMASSQ)
3396     ELSE
3397     DMASS = -SQRT(-DMASSQ)
3398     ENDIF
3399     IF (QMASS.EQ.0.0) THEN
3400     FMASS = -0.001
3401     ELSE
3402     DMASS = DMASS/(2.*QMASS)
3403     END IF
3404     100 CONTINUE
3405     RETURN
3406     END
3407     C======================================================================= =======
3408     SUBROUTINE CEMASSQ(NTRKQ,QMASS, PXYZE,IERR)
3409     C======================================================================= =======
3410     C EMASSQ calculates M**2, sigma(M**2), via a call th MCALC
3411     C This is furnished as a convenience for people who have calls to this
3412     C obsolescent routine. Note the more restrictive set of track pointers
3413     C as compared with MCALC.
3414     C----------------------------------------------------------------------- -------
3415     IMPLICIT NONE
3416     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
3417     #include "MitCommon/Ctvmft/interface/cctvmft.h"
3418     INTEGER NTRKQ, IERR
3419     REAL QMASS(MAXTRK), PXYZE(6)
3420     INTEGER I,N, MTRACK(MAXTRK)
3421     REAL FMASS, DMASS
3422     REAL*8 P4(4)
3423     C----------------------------------------------------------------------- -------
3424     IERR = 0
3425     CALL VZERO(P4, 2*4)
3426     CALL VZERO(PXYZE,6)
3427     N = MIN0(MaxTrk,NTRKQ)
3428     DO I=1,N
3429     MTRACK(I) = I
3430     TMASS(I) = QMASS(I)
3431     END DO
3432     CALL CMCALC (NTRKQ,MTRACK,FMASS,DMASS, P4)
3433     IF (FMASS.LT.0.0) THEN
3434     IERR = FMASS
3435     GO TO 900
3436     END IF
3437     DO I=1,4
3438     PXYZE(I) = P4(I)
3439     END DO
3440     PXYZE(5) = FMASS**2
3441     PXYZE(6) = 2.0 * FMASS * DMASS
3442     900 CONTINUE
3443     RETURN
3444     END
3445     C===============================================================================
3446     SUBROUTINE CDCALC (Nv,Mv,DXYZ,Dr,Dz,Dl)
3447     C===============================================================================
3448     C Auxialliary subroutine for use with CTVMFT.
3449     C Calculates the distance between the two vertices Nv, Mv and its error.
3450     C Mostly useful only if Nv "points at" Mv.
3451     C Input parameters: Nv, Mv The vertex indices.
3452     C The rest of the Input data comes from the common block /CTVMFT/
3453     C which must contain a valid fit
3454     C Output parameters:
3455     C DXYZ = (unrotated) x, y, and z components of vertex displacement
3456     C Dr = (signed) radial vertex separation (dot product of Dxy * VtxPxy)
3457     C Dz = (signed) vertex separation (dot product of Dz * VtxPz)
3458     C Dl = uncertainty of the three-vector (Dr,Dphi,Dz) (note Dphi~0)
3459     C-------------------------------------------------------------------------------
3460     IMPLICIT NONE
3461     #include "MitCommon/Ctvmft/interface/cctvmdi.h"
3462     #include "MitCommon/Ctvmft/interface/cctvmft.h"
3463     INTEGER Nv,Mv
3464     REAL Dxyz(3), Dr,Dz, Dl(3), FL(3), U
3465     INTEGER I,J,K, IERR, NvF,MvF
3466     REAL*8 S, ROT(3,3), E(3,3),F(3,3)
3467     CHARACTER*80 STRING
3468     C-------------------------------------------------------------------------------
3469     C Setup vertex offset pointers, check for primary
3470     IF (Nv.LT. 1 .OR. Nv.GT.NVERTX) THEN
3471     IERR = 99
3472     WRITE(STRING,900) Nv
3473     900 FORMAT(' Vertex Nv',I3,' is invalid')
3474     CALL CERROR ('DCALC ',IERR,STRING)
3475     ccc STOP
3476     ELSE IF (Mv.LT.0 .OR. Mv.GE.Nv) THEN
3477     IERR = 98
3478     WRITE(STRING,901) Mv
3479     901 FORMAT(' Vertex Mv',I3,' is invalid')
3480     CALL CERROR ('DCALC ',IERR,STRING)
3481     ccc STOP
3482     END IF
3483     DO I=1,9
3484     ROT(I,1) = 0.0D0
3485     END DO
3486     C Pointers to information in VMAT for the two vertices
3487     NvF = VOFF(Nv)
3488     IF (Mv.GT.0) THEN
3489     MvF = VOFF(Mv)
3490     ELSE
3491     MvF =-1
3492     DO I=1,NVERTX
3493     C the primary participated in this fit
3494     IF (VtxPnt(I,1).EQ.0) THEN
3495     MvF = 0
3496     END IF
3497     END DO
3498     END IF
3499     C covariance matrix on vertex separation
3500     DO I=1,3
3501     DO J=I,3
3502     E(I,J) = VMAT(NvF+I,NvF+J)
3503     IF (MvF.GE.0) THEN
3504     E(I,J) = E(I,J) + VMAT(MvF+I,MvF+J)
3505     E(I,J) = E(I,J) - VMAT(NvF+J,MvF+I) * 2.0D0
3506     ELSE
3507     E(I,J) = E(I,J) + EXYZPV(I,J)
3508     END IF
3509     E(J,I) = E(I,J)
3510     END DO
3511     END DO
3512     C vertex separation vector
3513     IF (MvF.GE.0) THEN
3514     DO I=1,3
3515     DXYZ(I) = XYZVRT(I,Nv) - XYZVRT(I,Mv)
3516     END DO
3517     ELSE
3518     DO I=1,3
3519     DXYZ(I) = XYZVRT(I,Nv) - XYZPV0(I)
3520     END DO
3521     END IF
3522     S = SQRT(DXYZ(1)**2 + DXYZ(2)**2)
3523     c If the two vertices have exactly the same x and y, then S is
3524     c zero and we need to protect against dividing by S. C. Blocker 11/20/03
3525     c if(s.le.0.) then
3526     IF (ABS(S).LE.1E-42) THEN
3527     dr = 0.
3528     dz = 0.
3529     dl(1) = -999.
3530     dl(2) = -999.
3531     dl(3) = -999.
3532     return
3533     endif
3534     ROT(1,1) = DXYZ(1)/S
3535     ROT(1,2) = DXYZ(2)/S
3536     ROT(2,1) =-ROT(1,2)
3537     ROT(2,2) = ROT(1,1)
3538     ROT(3,3) = 1.0D0
3539     do i=1,2
3540     s = 0.0D0
3541     do j=1,2
3542     s = s + rot(i,j)*DXYZ(J)
3543     end do
3544     fl(i) = s
3545     end do
3546     C pre and post multiply xy part
3547     DO I=1,2
3548     DO J=1,2
3549     S = 0.0D0
3550     DO K=1,2
3551     S = S + ROT(I,K) * E(K,J)
3552     END DO
3553     F(I,J) = S
3554     END DO
3555     END DO
3556     DO I=1,2
3557     DO J=1,2
3558     S = 0.0D0
3559     DO K=1,2
3560     S = S + F(I,K) * ROT(J,K)
3561     END DO
3562     E(I,J) = S
3563     END DO
3564     END DO
3565     U = DXYZ(1)*VtxP4(1,Nv) + DXYZ(2)*VtxP4(2,Nv)
3566     C (signed) xy vertex separation
3567     Dr = SIGN(SQRT(DXYZ(1)**2+DXYZ(2)**2),U)
3568     U = DXYZ(3)*VtxP4(3,Nv)
3569     C (signed) z vertex separation
3570     Dz = SIGN(ABS(DXYZ(3)),U)
3571     DO I=1,3
3572     IF (E(I,I).GT.0.0) THEN
3573     Dl(I) = SQRT(E(I,I))
3574     ELSE
3575     Dl(I) = 0.0
3576     END IF
3577     END DO
3578     RETURN
3579     END