/[PAMELA software]/DarthVader/TrackerLevel2/src/F77/mini.f
ViewVC logotype

Contents of /DarthVader/TrackerLevel2/src/F77/mini.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.8 - (show annotations) (download)
Tue Nov 21 14:00:40 2006 UTC (18 years ago) by pam-fi
Branch: MAIN
Changes since 1.7: +12 -3 lines
bug fixed + n.couple cut implemented

1 ************************************************************************
2 *
3 * subroutine to evaluate the vector alfa (AL)
4 * which minimizes CHI^2
5 *
6 * - modified from mini.f in order to call differente chi^2 routine.
7 * The new one includes also single clusters: in this case
8 * the residual is defined as the distance between the track and the
9 * segment AB associated to the single cluster.
10 *
11 *
12 ************************************************************************
13
14
15 SUBROUTINE MINI2(ISTEP,IFAIL,IPRINT)
16
17 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
18
19 include 'commontracker.f' !tracker general common
20 include 'common_mini_2.f' !common for the tracking procedure
21
22 c logical DEBUG
23 c common/dbg/DEBUG
24
25 parameter (dinf=1.d15) !just a huge number...
26 c------------------------------------------------------------------------
27 c variables used in the tracking procedure (mini and its subroutines)
28 c
29 c N.B.: in mini & C. (and in the following block of variables too)
30 c the plane ordering is reversed in respect of normal
31 c ordering, but they maintain their Z coordinates. so plane number 1 is
32 c the first one that a particle meets, and its Z coordinate is > 0
33 c------------------------------------------------------------------------
34 DATA ZINI/23.5/ !!! ***PP*** to be changed !z coordinate of the reference plane
35
36 c DATA XGOOD,YGOOD/nplanes*1.,nplanes*1./ !planes to be used in the tracking
37
38 DATA STEPAL/5*1.d-7/ !alpha vector step
39 DATA ISTEPMAX/100/ !maximum number of steps in the chi^2 minimization
40 DATA TOLL/1.d-8/ !tolerance in reaching the next plane during
41 * !the tracking procedure
42 DATA STEPMAX/100./ !maximum number of steps in the trackin gprocess
43
44 c DATA ALMAX/dinf,dinf,1.,dinf,dinf/ !limits on alpha vector components
45 c DATA ALMIN/-dinf,-dinf,-1.,-dinf,-dinf/ !"
46 DATA ALMAX/dinf,dinf,dinf,dinf,dinf/ !limits on alpha vector components
47 DATA ALMIN/-dinf,-dinf,-dinf,-dinf,-dinf/ !"
48
49 DIMENSION DAL(5) !increment of vector alfa
50 DIMENSION CHI2DD_R(4,4),CHI2D_R(4) !hessiano e gradiente di chi2
51
52 c elena--------
53 REAL*8 AVRESX,AVRESY
54 c elena--------
55
56 INTEGER IFLAG
57 c--------------------------------------------------------
58 c IFLAG =1 ---- chi2 derivatives computed by using
59 c incremental ratios and posxyz.f
60 c IFLAG =2 ---- the approximation of Golden is used
61 c (see chisq.f)
62 c
63 c NB: the two metods gives equivalent results BUT
64 c method 2 is faster!!
65 c--------------------------------------------------------
66 DATA IFLAG/2/
67
68 c LOGICAL TRKDEBUG,TRKVERBOSE
69 c COMMON/TRKD/TRKDEBUG,TRKVERBOSE
70 LOGICAL TRKDEBUG,TRKVERBOSE
71 COMMON/TRKD/TRKDEBUG,TRKVERBOSE
72
73 IF(IPRINT.EQ.1) THEN
74 TRKVERBOSE = .TRUE.
75 TRKDEBUG = .FALSE.
76 ELSEIF(IPRINT.EQ.2)THEN
77 TRKVERBOSE = .TRUE.
78 TRKDEBUG = .TRUE.
79 ELSE
80 TRKVERBOSE = .FALSE.
81 TRKDEBUG = .FALSE.
82 ENDIF
83
84 * ----------------------------------------------------------
85 * evaluate average spatial resolution
86 * ----------------------------------------------------------
87 AVRESX = RESXAV
88 AVRESY = RESYAV
89 DO IP=1,6
90 IF( XGOOD(IP).EQ.1 )THEN
91 NX=NX+1
92 AVRESX=AVRESX+RESX(IP)
93 ENDIF
94 IF(NX.NE.0)AVRESX=AVRESX/NX
95 IF( YGOOD(IP).EQ.1 )THEN
96 NY=NY+1
97 AVRESY=AVRESY+RESY(IP)
98 ENDIF
99 IF(NX.NE.0)AVRESY=AVRESY/NY
100 ENDDO
101
102 * ----------------------------------------------------------
103 * define ALTOL(5) ---> tolerances on state vector
104 *
105 * ----------------------------------------------------------
106 * changed in order to evaluate energy-dependent
107 * tolerances on all 5 parameters
108 FACT=100. !scale factor to define tolerance on alfa
109 c deflection error (see PDG)
110 DELETA1 = 0.01/0.3/0.4/0.4451**2*SQRT(720./(6.+4.))
111 DELETA2 = 0.016/0.3/0.4/0.4451*SQRT(0.4451/9.36)
112 c$$$ ALTOL(1) = AVRESX/FACT !al(1) = x
113 c$$$ ALTOL(2) = AVRESY/FACT !al(2) = y
114 c$$$ ALTOL(3) = DSQRT(AVRESX**2 !al(3)=sin(theta)
115 c$$$ $ +AVRESY**2)/44.51/FACT
116 c$$$ ALTOL(4) = ALTOL(3) !al(4)=phi
117 c deflection error (see PDG)
118 c$$$ DELETA1 = 0.01*AVRESX/0.3/0.4/0.4451**2*SQRT(720./(6.+4.))
119 c$$$ DELETA2 = 0.016/0.3/0.4/0.4451*SQRT(0.4451/9.36)
120 * ----------------------------------------------------------
121 *
122 ISTEP=0 !num. steps to minimize chi^2
123 JFAIL=0 !error flag
124
125 if(TRKDEBUG) print*,'guess: ',al
126 if(TRKDEBUG) print*,'mini2: step ',istep,chi2,1./AL(5)
127
128 *
129 * -----------------------
130 * START MINIMIZATION LOOP
131 * -----------------------
132 10 ISTEP=ISTEP+1 !<<<<<<<<<<<<<< NEW STEP !!
133
134 CALL CHISQ(IFLAG,JFAIL) !chi^2 and its derivatives
135 IF(JFAIL.NE.0) THEN
136 IFAIL=1
137 CHI2=-9999.
138 if(TRKVERBOSE)
139 $ PRINT *,'*** ERROR in mini *** wrong CHISQ'
140 RETURN
141 ENDIF
142
143 COST=1e-7
144 DO I=1,5
145 DO J=1,5
146 CHI2DD(I,J)=CHI2DD(I,J)*COST
147 ENDDO
148 CHI2D(I)=CHI2D(I)*COST
149 ENDDO
150
151 IF(PFIXED.EQ.0.) THEN
152
153 *------------------------------------------------------------*
154 * track fitting with FREE deflection
155 *------------------------------------------------------------*
156 CALL DSFACT(5,CHI2DD,5,IFA,DET,JFA) !CHI2DD matrix determinant
157 IF(IFA.NE.0) THEN !not positive-defined
158 if(TRKVERBOSE)then
159 PRINT *,
160 $ '*** ERROR in mini ***'//
161 $ 'on matrix inversion (not pos-def)'
162 $ ,DET
163 endif
164 IF(CHI2.EQ.0) CHI2=-9999.
165 IF(CHI2.GT.0) CHI2=-CHI2
166 IFAIL=1
167 RETURN
168 ENDIF
169 CALL DSFINV(5,CHI2DD,5) !CHI2DD matrix inversion
170 * *******************************************
171 * find new value of AL-pha
172 * *******************************************
173 DO I=1,5
174 DAL(I)=0.
175 DO J=1,5
176 DAL(I)=DAL(I)-CHI2DD(I,J)*CHI2D(J)
177 COV(I,J)=2.*COST*CHI2DD(I,J)
178 ENDDO
179 ENDDO
180 DO I=1,5
181 AL(I)=AL(I)+DAL(I)
182 ENDDO
183 *------------------------------------------------------------*
184 * track fitting with FIXED deflection
185 *------------------------------------------------------------*
186 ELSE
187 AL(5)=1./PFIXED
188 DO I=1,4
189 CHI2D_R(I)=CHI2D(I)
190 DO J=1,4
191 CHI2DD_R(I,J)=CHI2DD(I,J)
192 ENDDO
193 ENDDO
194 CALL DSFACT(4,CHI2DD_R,4,IFA,DET,JFA)
195 IF(IFA.NE.0) THEN
196 if(TRKVERBOSE)then
197 PRINT *,
198 $ '*** ERROR in mini ***'//
199 $ 'on matrix inversion (not pos-def)'
200 $ ,DET
201 endif
202 IF(CHI2.EQ.0) CHI2=-9999.
203 IF(CHI2.GT.0) CHI2=-CHI2
204 IFAIL=1
205 RETURN
206 ENDIF
207 CALL DSFINV(4,CHI2DD_R,4)
208 * *******************************************
209 * find new value of AL-pha
210 * *******************************************
211 DO I=1,4
212 DAL(I)=0.
213 DO J=1,4
214 DAL(I)=DAL(I)-CHI2DD_R(I,J)*CHI2D_R(J)
215 COV(I,J)=2.*COST*CHI2DD_R(I,J)
216 ENDDO
217 ENDDO
218 DAL(5)=0.
219 DO I=1,4
220 AL(I)=AL(I)+DAL(I)
221 ENDDO
222 ENDIF
223
224 if(TRKDEBUG) print*,'mini2: step ',istep,chi2,1./AL(5)
225
226 *------------------------------------------------------------*
227 * ---------------------------------------------------- *
228 *------------------------------------------------------------*
229 * check parameter bounds:
230 *------------------------------------------------------------*
231 DO I=1,5
232 IF(AL(I).GT.ALMAX(I).OR.AL(I).LT.ALMIN(I))THEN
233 if(TRKVERBOSE)then
234 PRINT*,' *** WARNING in mini *** '
235 PRINT*,'MINI_2 ==> AL(',I,') out of range'
236 PRINT*,' value: ',AL(I),
237 $ ' limits: ',ALMIN(I),ALMAX(I)
238 print*,'istep ',istep
239 endif
240 IF(CHI2.EQ.0) CHI2=-9999.
241 IF(CHI2.GT.0) CHI2=-CHI2
242 IFAIL=1
243 RETURN
244 ENDIF
245 ENDDO
246 *------------------------------------------------------------*
247 * check number of steps:
248 *------------------------------------------------------------*
249 IF(ISTEP.ge.ISTEPMAX) then
250 c$$$ IFAIL=1
251 c$$$ if(TRKVERBOSE)
252 c$$$ $ PRINT *,'*** WARNING in mini *** ISTEP.GT.ISTEPMAX=',
253 c$$$ $ ISTEPMAX
254 goto 11
255 endif
256 *------------------------------------------------------------*
257 * ---------------------------------------------
258 * evaluate deflection tolerance on the basis of
259 * estimated deflection
260 * ---------------------------------------------
261 *------------------------------------------------------------*
262 c$$$ ALTOL(5) = DSQRT(DELETA1**2+DELETA2**2*AL(5)**2)/FACT
263 ALTOL(5) = DSQRT((DELETA1*AVRESX)**2+DELETA2**2*AL(5)**2)/FACT
264 ALTOL(1) = ALTOL(5)/DELETA1
265 ALTOL(2) = ALTOL(1)
266 ALTOL(3) = DSQRT(ALTOL(1)**2+ALTOL(2)**2)/44.51
267 ALTOL(4) = ALTOL(3)
268
269 *---- check tolerances:
270 c$$$ DO I=1,5
271 c$$$ if(TRKVERBOSE)print*,i,' -- ',DAL(I),ALTOL(I) !>>>> new step!
272 c$$$ ENDDO
273 c$$$ print*,'chi2 -- ',DCHI2
274
275 DO I=1,5
276 IF(ABS(DAL(I)).GT.ALTOL(I))GOTO 10 !>>>> new step!
277 ENDDO
278
279 * new estimate of chi^2:
280 JFAIL=0 !error flag
281 CALL CHISQ(IFLAG,JFAIL) !chi^2 and its derivatives
282 IF(JFAIL.NE.0) THEN
283 IFAIL=1
284 if(TRKVERBOSE)THEN
285 CHI2=-9999.
286 if(TRKVERBOSE)
287 $ PRINT *,'*** ERROR in mini *** wrong CHISQ'
288 ENDIF
289 RETURN
290 ENDIF
291 COST=1e-7
292 DO I=1,5
293 DO J=1,5
294 CHI2DD(I,J)=CHI2DD(I,J)*COST
295 ENDDO
296 CHI2D(I)=CHI2D(I)*COST
297 ENDDO
298 IF(PFIXED.EQ.0.) THEN
299 CALL DSFACT(5,CHI2DD,5,IFA,DET,JFA) !CHI2DD matrix determinant
300 IF(IFA.NE.0) THEN !not positive-defined
301 if(TRKVERBOSE)then
302 PRINT *,
303 $ '*** ERROR in mini ***'//
304 $ 'on matrix inversion (not pos-def)'
305 $ ,DET
306 endif
307 IF(CHI2.EQ.0) CHI2=-9999.
308 IF(CHI2.GT.0) CHI2=-CHI2
309 IFAIL=1
310 RETURN
311 ENDIF
312 CALL DSFINV(5,CHI2DD,5) !CHI2DD matrix inversion
313 DO I=1,5
314 DAL(I)=0.
315 DO J=1,5
316 COV(I,J)=2.*COST*CHI2DD(I,J)
317 ENDDO
318 ENDDO
319 ELSE
320 DO I=1,4
321 CHI2D_R(I)=CHI2D(I)
322 DO J=1,4
323 CHI2DD_R(I,J)=CHI2DD(I,J)
324 ENDDO
325 ENDDO
326 CALL DSFACT(4,CHI2DD_R,4,IFA,DET,JFA)
327 IF(IFA.NE.0) THEN
328 if(TRKVERBOSE)then
329 PRINT *,
330 $ '*** ERROR in mini ***'//
331 $ 'on matrix inversion (not pos-def)'
332 $ ,DET
333 endif
334 IF(CHI2.EQ.0) CHI2=-9999.
335 IF(CHI2.GT.0) CHI2=-CHI2
336 IFAIL=1
337 RETURN
338 ENDIF
339 CALL DSFINV(4,CHI2DD_R,4)
340 DO I=1,4
341 DAL(I)=0.
342 DO J=1,4
343 COV(I,J)=2.*COST*CHI2DD_R(I,J)
344 ENDDO
345 ENDDO
346 ENDIF
347 *****************************
348
349 * ------------------------------------
350 * Number of Degree Of Freedom
351 ndof=0
352 do ip=1,nplanes
353 ndof=ndof
354 $ +int(xgood(ip))
355 $ +int(ygood(ip))
356 enddo
357 if(pfixed.eq.0.) ndof=ndof-5 ! ***PP***
358 if(pfixed.ne.0.) ndof=ndof-4 ! ***PP***
359 if(ndof.le.0.) then
360 ndof = 1
361 if(TRKVERBOSE)
362 $ print*,'*** WARNING *** in mini n.dof = 0 (set to 1)'
363 endif
364
365 if(TRKDEBUG) print*,'mini2: -ok- ',istep,chi2,1./AL(5)
366
367 * ------------------------------------
368 * Reduced chi^2
369 CHI2 = CHI2/dble(ndof)
370
371 c print*,'mini2: chi2 ',chi2
372
373 11 CONTINUE
374
375 NSTEP=ISTEP ! ***PP***
376
377 RETURN
378 END
379
380 ******************************************************************************
381 *
382 * routine to compute chi^2 and its derivatives
383 *
384 *
385 * (modified in respect to the previous one in order to include
386 * single clusters. In this case the residual is evaluated by
387 * calculating the distance between the track intersection and the
388 * segment AB associated to the single cluster)
389 *
390 ******************************************************************************
391
392 SUBROUTINE CHISQ(IFLAG,IFAIL)
393
394 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
395
396 include 'commontracker.f' !tracker general common
397 include 'common_mini_2.f' !common for the tracking procedure
398
399 DIMENSION XV2(nplanes),YV2(nplanes),XV1(nplanes),YV1(nplanes)
400 $ ,XV0(nplanes),YV0(nplanes)
401 DIMENSION AL_P(5)
402
403 c LOGICAL TRKVERBOSE
404 c COMMON/TRKD/TRKVERBOSE
405 LOGICAL TRKDEBUG,TRKVERBOSE
406 COMMON/TRKD/TRKDEBUG,TRKVERBOSE
407 *
408 * chi^2 computation
409 *
410 DO I=1,5
411 AL_P(I)=AL(I)
412 ENDDO
413 JFAIL=0 !error flag
414 CALL POSXYZ(AL_P,JFAIL) !track intersection with tracking planes
415 IF(JFAIL.NE.0) THEN
416 IF(TRKVERBOSE)
417 $ PRINT *,'CHISQ ==> error from trk routine POSXYZ !!'
418 IFAIL=1
419 RETURN
420 ENDIF
421 DO I=1,nplanes
422 XV0(I)=XV(I)
423 YV0(I)=YV(I)
424 ENDDO
425 * ------------------------------------------------
426 c$$$ CHI2=0.
427 c$$$ DO I=1,nplanes
428 c$$$ CHI2=CHI2
429 c$$$ + +(XV(I)-XM(I))**2/RESX(i)**2 *XGOOD(I)*YGOOD(I)
430 c$$$ + +(YV(I)-YM(I))**2/RESY(i)**2 *YGOOD(I)*XGOOD(I)
431 c$$$ ENDDO
432 * ---------------------------------------------------------
433 * For planes with only a X or Y-cl included, instead of
434 * a X-Y couple, the residual for chi^2 calculation is
435 * evaluated by finding the point x-y, along the segment AB,
436 * closest to the track.
437 * The X or Y coordinate, respectivelly for X and Y-cl, is
438 * then assigned to XM or YM, which is then considered the
439 * measured position of the cluster.
440 * ---------------------------------------------------------
441 CHI2=0.
442 DO I=1,nplanes
443 IF(XGOOD(I).EQ.1.AND.YGOOD(I).EQ.0)THEN !X-cl
444 BETA = (XM_B(I)-XM_A(I))/(YM_B(I)-YM_A(I))
445 ALFA = XM_A(I) - BETA * YM_A(I)
446 YM(I) = ( YV(I) + BETA*XV(I) - BETA*ALFA )/(1+BETA**2)
447 if(YM(I).lt.dmin1(YM_A(I),YM_B(I)))
448 $ YM(I)=dmin1(YM_A(I),YM_B(I))
449 if(YM(I).gt.dmax1(YM_A(I),YM_B(I)))
450 $ YM(I)=dmax1(YM_A(I),YM_B(I))
451 XM(I) = ALFA + BETA * YM(I) !<<<< measured coordinates
452 ELSEIF(XGOOD(I).EQ.0.AND.YGOOD(I).EQ.1)THEN !Y-cl
453 BETA = (YM_B(I)-YM_A(I))/(XM_B(I)-XM_A(I))
454 ALFA = YM_A(I) - BETA * XM_A(I)
455 XM(I) = ( XV(I) + BETA*YV(I) - BETA*ALFA )/(1+BETA**2)
456 if(XM(I).lt.dmin1(XM_A(I),XM_B(I)))
457 $ XM(I)=dmin1(XM_A(I),XM_B(I))
458 if(XM(I).gt.dmax1(XM_A(I),XM_B(I)))
459 $ XM(I)=dmax1(XM_A(I),XM_B(I))
460 YM(I) = ALFA + BETA * XM(I) !<<<< measured coordinates
461 ENDIF
462 CHI2=CHI2
463 + +(XV(I)-XM(I))**2/RESX(i)**2 *( XGOOD(I)*YGOOD(I) )
464 + +(YV(I)-YM(I))**2/RESY(i)**2 *( YGOOD(I)*XGOOD(I) )
465 + +((XV(I)-XM(I))**2+(YV(I)-YM(I))**2)/RESX(i)**2
466 + *( XGOOD(I)*(1-YGOOD(I)) )
467 + +((XV(I)-XM(I))**2+(YV(I)-YM(I))**2)/RESY(i)**2
468 + *( (1-XGOOD(I))*YGOOD(I) )
469 ENDDO
470 c print*,'CHISQ ',chi2
471 * ------------------------------------------------
472 *
473 * calculation of derivatives (dX/dAL_fa and dY/dAL_fa)
474 *
475 * //////////////////////////////////////////////////
476 * METHOD 1 -- incremental ratios
477 * //////////////////////////////////////////////////
478
479 IF(IFLAG.EQ.1) THEN
480
481 DO J=1,5
482 DO JJ=1,5
483 AL_P(JJ)=AL(JJ)
484 ENDDO
485 AL_P(J)=AL_P(J)+STEPAL(J)/2.
486 JFAIL=0
487 CALL POSXYZ(AL_P,JFAIL)
488 IF(JFAIL.NE.0) THEN
489 IF(TRKVERBOSE)
490 *23456789012345678901234567890123456789012345678901234567890123456789012
491 $ PRINT *,'CHISQ ==> error from trk routine POSXYZ'
492 IFAIL=1
493 RETURN
494 ENDIF
495 DO I=1,nplanes
496 XV2(I)=XV(I)
497 YV2(I)=YV(I)
498 ENDDO
499 AL_P(J)=AL_P(J)-STEPAL(J)
500 JFAIL=0
501 CALL POSXYZ(AL_P,JFAIL)
502 IF(JFAIL.NE.0) THEN
503 IF(TRKVERBOSE)
504 $ PRINT *,'CHISQ ==> error from trk routine POSXYZ'
505 IFAIL=1
506 RETURN
507 ENDIF
508 DO I=1,nplanes
509 XV1(I)=XV(I)
510 YV1(I)=YV(I)
511 ENDDO
512 DO I=1,nplanes
513 DXDAL(I,J)=(XV2(I)-XV1(I))/STEPAL(J)
514 DYDAL(I,J)=(YV2(I)-YV1(I))/STEPAL(J)
515 ENDDO
516 ENDDO
517
518 ENDIF
519
520 * //////////////////////////////////////////////////
521 * METHOD 2 -- Bob Golden
522 * //////////////////////////////////////////////////
523
524 IF(IFLAG.EQ.2) THEN
525
526 DO I=1,nplanes
527 DXDAL(I,1)=1.
528 DYDAL(I,1)=0.
529
530 DXDAL(I,2)=0.
531 DYDAL(I,2)=1.
532
533 COSTHE=DSQRT(1.-AL(3)**2)
534 IF(COSTHE.EQ.0.) THEN
535 IF(TRKVERBOSE)PRINT *,'=== WARNING ===> COSTHE=0'
536 IFAIL=1
537 RETURN
538 ENDIF
539
540 DXDAL(I,3)=(ZINI-ZM(I))*DCOS(AL(4))/COSTHE**3
541 DYDAL(I,3)=(ZINI-ZM(I))*DSIN(AL(4))/COSTHE**3
542
543 DXDAL(I,4)=-AL(3)*(ZINI-ZM(I))*DSIN(AL(4))/COSTHE
544 DYDAL(I,4)=AL(3)*(ZINI-ZM(I))*DCOS(AL(4))/COSTHE
545
546 IF(AL(5).NE.0.) THEN
547 DXDAL(I,5)=
548 + (XV(I)-(AL(1)+AL(3)/COSTHE*(ZINI-ZM(I))
549 + *DCOS(AL(4))))/AL(5)
550 DYDAL(I,5)=
551 + (YV(I)-(AL(2)+AL(3)/COSTHE*(ZINI-ZM(I))
552 + *DSIN(AL(4))))/AL(5)
553 ELSE
554 DXDAL(I,5)=100.*( 0.25 *0.3*0.4*(0.01*(ZINI-ZM(I)))**2 )
555 DYDAL(I,5)=0.
556 ENDIF
557
558 ENDDO
559 ENDIF
560 *
561 * x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x
562 * >>> CHI2D evaluation
563 *
564 DO J=1,5
565 CHI2D(J)=0.
566 DO I=1,nplanes
567 CHI2D(J)=CHI2D(J)
568 + +2.*(XV0(I)-XM(I))/RESX(i)**2*DXDAL(I,J) *XGOOD(I)
569 + +2.*(YV0(I)-YM(I))/RESY(i)**2*DYDAL(I,J) *YGOOD(I)
570 ENDDO
571 ENDDO
572 *
573 * >>> CHI2DD evaluation
574 *
575 DO I=1,5
576 DO J=1,5
577 CHI2DD(I,J)=0.
578 DO K=1,nplanes
579 CHI2DD(I,J)=CHI2DD(I,J)
580 + +2.*DXDAL(K,I)*DXDAL(K,J)/RESX(k)**2 *XGOOD(K)
581 + +2.*DYDAL(K,I)*DYDAL(K,J)/RESY(k)**2 *YGOOD(K)
582 ENDDO
583 ENDDO
584 ENDDO
585 * x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x-x
586
587 RETURN
588 END
589
590
591 *****************************************************************
592 *
593 * Routine to compute the track intersection points
594 * on the tracking-system planes, given the track parameters
595 *
596 * The routine is based on GRKUTA, which computes the
597 * trajectory of a charged particle in a magnetic field
598 * by solving the equatins of motion with Runge-Kuta method.
599 *
600 * Variables that have to be assigned when the subroutine
601 * is called are:
602 *
603 * ZM(1,NPLANES) ----> z coordinates of the planes
604 * AL_P(1,5) ----> track-parameter vector
605 *
606 * -----------------------------------------------------------
607 * NB !!!
608 * The routine works properly only if the
609 * planes are numbered in descending order starting from the
610 * reference plane (ZINI)
611 * -----------------------------------------------------------
612 *
613 *****************************************************************
614
615 SUBROUTINE POSXYZ(AL_P,IFAIL)
616
617 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
618
619 include 'commontracker.f' !tracker general common
620 include 'common_mini_2.f' !common for the tracking procedure
621
622 c LOGICAL TRKVERBOSE
623 c COMMON/TRKD/TRKVERBOSE
624 LOGICAL TRKDEBUG,TRKVERBOSE
625 COMMON/TRKD/TRKDEBUG,TRKVERBOSE
626 c
627 DIMENSION AL_P(5)
628 *
629 DO I=1,nplanes
630 ZV(I)=ZM(I) !
631 ENDDO
632 *
633 * set parameters for GRKUTA
634 *
635 IF(AL_P(5).NE.0) CHARGE=AL_P(5)/DABS(AL_P(5))
636 IF(AL_P(5).EQ.0) CHARGE=1.
637 VOUT(1)=AL_P(1)
638 VOUT(2)=AL_P(2)
639 VOUT(3)=ZINI ! DBLE(Z0)-DBLE(ZSPEC)
640 VOUT(4)=AL_P(3)*DCOS(AL_P(4))
641 VOUT(5)=AL_P(3)*DSIN(AL_P(4))
642 VOUT(6)=-1.*DSQRT(1.-AL_P(3)**2)
643 IF(AL_P(5).NE.0.) VOUT(7)=DABS(1./AL_P(5))
644 IF(AL_P(5).EQ.0.) VOUT(7)=1.E8
645
646 c$$$ print*,'POSXY ',vout
647
648 DO I=1,nplanes
649 step=vout(3)-zv(i)
650 10 DO J=1,7
651 VECT(J)=VOUT(J)
652 VECTINI(J)=VOUT(J)
653 ENDDO
654 11 continue
655 CALL GRKUTA(CHARGE,STEP,VECT,VOUT)
656 IF(VOUT(3).GT.VECT(3)) THEN
657 IFAIL=1
658 if(TRKVERBOSE)
659 $ PRINT *,'posxy (grkuta): WARNING ===> backward track!!'
660 c$$$ if(.TRUE.)print*,'charge',charge
661 c$$$ if(.TRUE.)print*,'vect',vect
662 c$$$ if(.TRUE.)print*,'vout',vout
663 c$$$ if(.TRUE.)print*,'step',step
664 if(TRKVERBOSE)print*,'charge',charge
665 if(TRKVERBOSE)print*,'vect',vect
666 if(TRKVERBOSE)print*,'vout',vout
667 if(TRKVERBOSE)print*,'step',step
668 RETURN
669 ENDIF
670 Z=VOUT(3)
671 IF(Z.LE.ZM(I)+TOLL.AND.Z.GE.ZM(I)-TOLL) GOTO 100
672 IF(Z.GT.ZM(I)+TOLL) GOTO 10
673 IF(Z.LE.ZM(I)-TOLL) THEN
674 STEP=STEP*(ZM(I)-VECT(3))/(Z-VECT(3))
675 DO J=1,7
676 VECT(J)=VECTINI(J)
677 ENDDO
678 GOTO 11
679 ENDIF
680
681 * -----------------------------------------------
682 * evaluate track coordinates
683 100 XV(I)=VOUT(1)
684 YV(I)=VOUT(2)
685 ZV(I)=VOUT(3)
686 AXV(I)=DATAN(VOUT(4)/VOUT(6))*180./ACOS(-1.)
687 AYV(I)=DATAN(VOUT(5)/VOUT(6))*180./ACOS(-1.)
688 * -----------------------------------------------
689
690 ENDDO
691
692 RETURN
693 END
694
695
696
697
698
699 * **********************************************************
700 * Some initialization routines
701 * **********************************************************
702
703 * ----------------------------------------------------------
704 * Routine to initialize COMMON/TRACK/
705 *
706 subroutine track_init
707
708 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
709
710 include 'commontracker.f' !tracker general common
711 include 'common_mini_2.f' !common for the tracking procedure
712 include 'common_mech.f'
713
714 do i=1,5
715 AL(i) = 0.
716 enddo
717
718 do ip=1,NPLANES
719 ZM(IP) = fitz(nplanes-ip+1) !init to mech. position
720 XM(IP) = -100. !0.
721 YM(IP) = -100. !0.
722 XM_A(IP) = -100. !0.
723 YM_A(IP) = -100. !0.
724 c ZM_A(IP) = 0
725 XM_B(IP) = -100. !0.
726 YM_B(IP) = -100. !0.
727 c ZM_B(IP) = 0
728 RESX(IP) = 1000. !3.d-4
729 RESY(IP) = 1000. !12.d-4
730 XGOOD(IP) = 0
731 YGOOD(IP) = 0
732 enddo
733
734 return
735 end
736
737
738 ***************************************************
739 * *
740 * *
741 * *
742 * *
743 * *
744 * *
745 **************************************************
746
747 subroutine guess()
748
749 c IMPLICIT DOUBLE PRECISION (A-H,O-Z)
750
751 include 'commontracker.f' !tracker general common
752 include 'common_mini_2.f' !common for the tracking procedure
753
754 REAL*4 XP(NPLANES),ZP(NPLANES),AP(NPLANES),RP(NPLANES)
755 REAL*4 CHI,XC,ZC,RADIUS
756 * ----------------------------------------
757 * Y view
758 * ----------------------------------------
759 * ----------------------------------------
760 * initial guess with a straigth line
761 * ----------------------------------------
762 SZZ=0.
763 SZY=0.
764 SSY=0.
765 SZ=0.
766 S1=0.
767 DO I=1,nplanes
768 IF(YGOOD(I).EQ.1)THEN
769 YY = YM(I)
770 IF(XGOOD(I).EQ.0)THEN
771 YY = (YM_A(I) + YM_B(I))/2
772 ENDIF
773 SZZ=SZZ+ZM(I)*ZM(I)
774 SZY=SZY+ZM(I)*YY
775 SSY=SSY+YY
776 SZ=SZ+ZM(I)
777 S1=S1+1.
778 ENDIF
779 ENDDO
780 DET=SZZ*S1-SZ*SZ
781 AY=(SZY*S1-SZ*SSY)/DET
782 BY=(SZZ*SSY-SZY*SZ)/DET
783 Y0 = AY*ZINI+BY
784 * ----------------------------------------
785 * X view
786 * ----------------------------------------
787 * ----------------------------------------
788 * 1) initial guess with a circle
789 * ----------------------------------------
790 NP=0
791 DO I=1,nplanes
792 IF(XGOOD(I).EQ.1)THEN
793 XX = XM(I)
794 IF(YGOOD(I).EQ.0)THEN
795 XX = (XM_A(I) + XM_B(I))/2
796 ENDIF
797 NP=NP+1
798 XP(NP)=XX
799 ZP(NP)=ZM(I)
800 ENDIF
801 ENDDO
802 CALL TRICIRCLE(NP,XP,ZP,AP,RP,CHI,XC,ZC,RADIUS,IFLAG)
803 print*,' circle: ',XC,ZC,RADIUS,' --- ',CHI,IFLAG
804 IF(IFLAG.NE.0)GOTO 10 !straigth fit
805 if(CHI.gt.100)GOTO 10 !straigth fit
806 ARG = RADIUS**2-(ZINI-ZC)**2
807 IF(ARG.LT.0)GOTO 10 !straigth fit
808 DC = SQRT(ARG)
809 IF(XC.GT.0)DC=-DC
810 X0=XC+DC
811 AX = -(ZINI-ZC)/DC
812 DEF=100./(RADIUS*0.3*0.43)
813 IF(XC.GT.0)DEF=-DEF
814
815 IF(ABS(X0).GT.30)THEN
816 PRINT*,'STRANGE GUESS: XC,ZC,R ',XC,ZC,RADIUS
817 $ ,' - CHI ',CHI,' - X0,AX,DEF ',X0,AX,DEF
818 GOTO 10 !straigth fit
819 ENDIF
820 GOTO 20 !guess is ok
821
822 * ----------------------------------------
823 * 2) initial guess with a straigth line
824 * - if circle does not intersect reference plane
825 * - if bad chi**2
826 * ----------------------------------------
827 10 CONTINUE
828 SZZ=0.
829 SZX=0.
830 SSX=0.
831 SZ=0.
832 S1=0.
833 DO I=1,nplanes
834 IF(XGOOD(I).EQ.1)THEN
835 XX = XM(I)
836 IF(YGOOD(I).EQ.0)THEN
837 XX = (XM_A(I) + XM_B(I))/2
838 ENDIF
839 SZZ=SZZ+ZM(I)*ZM(I)
840 SZX=SZX+ZM(I)*XX
841 SSX=SSX+XX
842 SZ=SZ+ZM(I)
843 S1=S1+1.
844 ENDIF
845 ENDDO
846 DET=SZZ*S1-SZ*SZ
847 AX=(SZX*S1-SZ*SSX)/DET
848 BX=(SZZ*SSX-SZX*SZ)/DET
849 DEF = 0
850 X0 = AX*ZINI+BX
851
852 20 CONTINUE
853 * ----------------------------------------
854 * guess
855 * ----------------------------------------
856
857 AL(1) = X0
858 AL(2) = Y0
859 tath = sqrt(AY**2+AX**2)
860 AL(3) = tath/sqrt(1+tath**2)
861 IF(AX.NE.0)THEN
862 AL(4)= atan(AY/AX)
863 ELSE
864 AL(4) = acos(-1.)/2
865 IF(AY.LT.0)AL(4) = AL(4)+acos(-1.)
866 ENDIF
867 IF(AX.LT.0)AL(4)= acos(-1.)+ AL(4)
868 AL(4) = -acos(-1.) + AL(4) !from incidence direction to tracking rs
869 AL(5) = DEF
870
871 c print*,' guess: ',(al(i),i=1,5)
872
873 end

  ViewVC Help
Powered by ViewVC 1.1.23