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

Annotation of /DarthVader/TrackerLevel2/src/F77/analysissubroutines.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1.24 - (hide annotations) (download)
Tue May 15 16:22:18 2007 UTC (17 years, 7 months ago) by pam-fi
Branch: MAIN
CVS Tags: v3r05, v3r06
Changes since 1.23: +4 -2 lines
*** empty log message ***

1 mocchiut 1.1 ************************************************************
2     * The following subroutines
3     * - track_finding >> hough transform
4     * - track_fitting >> bob golden fitting
5     * all the procedures to create LEVEL2 data, starting from LEVEL1 data.
6     *
7     *
8     *
9     * (This subroutine and all the dependent subroutines
10     * will be included in the flight software)
11     ************************************************************
12     subroutine track_finding(iflag)
13    
14     include 'commontracker.f'
15 pam-fi 1.9 include 'level1.f'
16 mocchiut 1.1 include 'common_momanhough.f'
17     include 'common_mech.f'
18     include 'common_xyzPAM.f'
19     include 'common_mini_2.f'
20     include 'calib.f'
21     include 'level2.f'
22    
23 pam-fi 1.20
24    
25     c print*,'======================================================'
26     c$$$ do ic=1,NCLSTR1
27     c$$$ if(.false.
28     c$$$ $ .or.nsatstrips(ic).gt.0
29     c$$$c $ .or.nbadstrips(0,ic).gt.0
30     c$$$c $ .or.nbadstrips(4,ic).gt.0
31     c$$$c $ .or.nbadstrips(3,ic).gt.0
32     c$$$ $ .or..false.)then
33     c$$$ print*,'--- cl-',ic,' ------------------------'
34     c$$$ istart = INDSTART(IC)
35     c$$$ istop = TOTCLLENGTH
36     c$$$ if(ic.lt.NCLSTR1)istop=INDSTART(IC+1)-1
37     c$$$ print*,'ADC ',(CLADC(i),i=istart,istop)
38     c$$$ print*,'s/n ',(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)
39     c$$$ print*,'sgnl ',(CLSIGNAL(i),i=istart,istop)
40     c$$$ print*,'strip ',(i-INDMAX(ic),i=istart,istop)
41     c$$$ print*,'view ',VIEW(ic)
42     c$$$ print*,'maxs ',MAXS(ic)
43     c$$$ print*,'COG4 ',cog(4,ic)
44     c$$$ ff = fbad_cog(4,ic)
45     c$$$ print*,'fbad ',ff
46     c$$$ print*,(CLBAD(i),i=istart,istop)
47     c$$$ bb=nbadstrips(0,ic)
48     c$$$ print*,'#BAD (tot)',bb
49     c$$$ bb=nbadstrips(4,ic)
50     c$$$ print*,'#BAD (4)',bb
51     c$$$ bb=nbadstrips(3,ic)
52     c$$$ print*,'#BAD (3)',bb
53     c$$$ ss=nsatstrips(ic)
54     c$$$ print*,'#saturated ',ss
55     c$$$ endif
56     c$$$ enddo
57 mocchiut 1.1
58     *-------------------------------------------------------------------------------
59     * STEP 1
60     *-------------------------------------------------------------------------------
61     * X-Y cluster association
62     *
63     * Clusters are associated to form COUPLES
64     * Clusters not associated in any couple are called SINGLETS
65     *
66     * Track identification (Hough transform) and fitting is first done on couples.
67     * Hence singlets are possibly added to the track.
68     *
69     * Variables assigned by the routine "cl_to_couples" are those in the
70     * common blocks:
71     * - common/clusters/cl_good
72     * - common/couples/clx,cly,ncp_plane,ncp_tot,cp_useds1,cp_useds2
73     * - common/singlets/ncls,cls,cl_single
74     *-------------------------------------------------------------------------------
75     *-------------------------------------------------------------------------------
76    
77 pam-fi 1.20
78 mocchiut 1.1 call cl_to_couples(iflag)
79     if(iflag.eq.1)then !bad event
80 pam-fi 1.9 goto 880 !go to next event
81 mocchiut 1.1 endif
82    
83     *-----------------------------------------------------
84     *-----------------------------------------------------
85     * HOUGH TRASFORM
86     *-----------------------------------------------------
87     *-----------------------------------------------------
88    
89    
90     *-------------------------------------------------------------------------------
91     * STEP 2
92     *-------------------------------------------------------------------------------
93     *
94     * Association of couples to form
95     * - DOUBLETS in YZ view
96     * - TRIPLETS in XZ view
97     *
98     * Variables assigned by the routine "cp_to_doubtrip" are those in the
99     * common blocks:
100     * - common/hough_param/
101     * $ alfayz1, !Y0
102     * $ alfayz2, !tg theta-yz
103     * $ alfaxz1, !X0
104     * $ alfaxz2, !tg theta-xz
105     * $ alfaxz3 !1/r
106     * - common/doublets/ndblt,cpyz1,cpyz2
107     * - common/triplets/ntrpt,cpxz1,cpxz2,cpxz3
108     *-------------------------------------------------------------------------------
109     *-------------------------------------------------------------------------------
110    
111 pam-fi 1.20
112 mocchiut 1.1 call cp_to_doubtrip(iflag)
113     if(iflag.eq.1)then !bad event
114 pam-fi 1.9 goto 880 !go to next event
115 mocchiut 1.1 endif
116    
117    
118     *-------------------------------------------------------------------------------
119     * STEP 3
120     *-------------------------------------------------------------------------------
121     *
122     * Classification of doublets and triplets to form CLOUDS,
123     * according to distance in parameter space.
124     *
125     * cloud = cluster of points (doublets/triplets) in parameter space
126     *
127     *
128     *
129     * Variables assigned by the routine "doub_to_YZcloud" are those in the
130     * common blocks:
131     * - common/clouds_yz/
132     * $ nclouds_yz
133     * $ ,alfayz1_av,alfayz2_av
134     * $ ,ptcloud_yz,db_cloud,cpcloud_yz
135     *
136     * Variables assigned by the routine "trip_to_XZcloud" are those in the
137     * common blocks:
138     * common/clouds_xz/
139     * $ nclouds_xz xz2_av,alfaxz3_av
140     * $ ,ptcloud_xz,tr_cloud,cpcloud_xz
141     *-------------------------------------------------------------------------------
142     *-------------------------------------------------------------------------------
143 pam-fi 1.9 * count number of hit planes
144     planehit=0
145     do np=1,nplanes
146     if(ncp_plane(np).ne.0)then
147     planehit=planehit+1
148     endif
149     enddo
150     if(planehit.lt.3) goto 880 ! exit
151    
152     nptxz_min=x_min_start
153     nplxz_min=x_min_start
154    
155     nptyz_min=y_min_start
156     nplyz_min=y_min_start
157    
158     cutdistyz=cutystart
159     cutdistxz=cutxstart
160 mocchiut 1.1
161 pam-fi 1.9 878 continue
162 mocchiut 1.1 call doub_to_YZcloud(iflag)
163     if(iflag.eq.1)then !bad event
164     goto 880 !fill ntp and go to next event
165 pam-fi 1.9 endif
166     if(nclouds_yz.eq.0.and.cutdistyz.lt.maxcuty)then
167     if(cutdistyz.lt.maxcuty/2)then
168     cutdistyz=cutdistyz+cutystep
169     else
170     cutdistyz=cutdistyz+(3*cutystep)
171     endif
172     goto 878
173     endif
174    
175     if(planehit.eq.3) goto 881
176    
177     879 continue
178 mocchiut 1.1 call trip_to_XZcloud(iflag)
179     if(iflag.eq.1)then !bad event
180     goto 880 !fill ntp and go to next event
181     endif
182 pam-fi 1.9
183     if(nclouds_xz.eq.0.and.cutdistxz.lt.maxcutx)then
184     cutdistxz=cutdistxz+cutxstep
185     goto 879
186     endif
187    
188    
189     881 continue
190     * if there is at least three planes on the Y view decreases cuts on X view
191     if(nclouds_xz.eq.0.and.nclouds_yz.gt.0.and.
192     $ nplxz_min.ne.y_min_start)then
193     nptxz_min=x_min_step
194     nplxz_min=x_min_start-x_min_step
195     goto 879
196     endif
197    
198 mocchiut 1.1 880 return
199     end
200    
201     ************************************************************
202    
203    
204     subroutine track_fitting(iflag)
205    
206     include 'commontracker.f'
207 pam-fi 1.9 include 'level1.f'
208 mocchiut 1.1 include 'common_momanhough.f'
209     include 'common_mech.f'
210     include 'common_xyzPAM.f'
211     include 'common_mini_2.f'
212     include 'calib.f'
213     include 'level2.f'
214    
215 pam-fi 1.9 c include 'momanhough_init.f'
216 mocchiut 1.1
217     logical FIMAGE !
218 pam-fi 1.11 real*8 AL_GUESS(5)
219 mocchiut 1.1
220     *-------------------------------------------------------------------------------
221     * STEP 4 (ITERATED until any other physical track isn't found)
222     *-------------------------------------------------------------------------------
223     *
224     * YZ and XZ clouds are combined in order to obtain the initial guess
225     * of the candidate-track parameters.
226     * A minimum number of matching couples between YZ and XZ clouds is required.
227     *
228     * A TRACK CANDIDATE is defined by
229     * - the couples resulting from the INTERSECTION of the two clouds, and
230     * - the associated track parameters (evaluated by performing a zero-order
231     * track fitting)
232     *
233     * The NTRACKS candidate-track parameters are stored in common block:
234     *
235     * - common/track_candidates/NTRACKS,AL_STORE
236     * $ ,XV_STORE,YV_STORE,ZV_STORE
237     * $ ,XM_STORE,YM_STORE,ZM_STORE
238     * $ ,RESX_STORE,RESY_STORE
239     * $ ,AXV_STORE,AYV_STORE
240     * $ ,XGOOD_STORE,YGOOD_STORE
241     * $ ,CP_STORE,RCHI2_STORE
242     *
243     *-------------------------------------------------------------------------------
244     *-------------------------------------------------------------------------------
245     ntrk=0 !counter of identified physical tracks
246    
247     11111 continue !<<<<<<< come here when performing a new search
248    
249     c iflag=0
250     call clouds_to_ctrack(iflag)
251     if(iflag.eq.1)then !no candidate tracks found
252     goto 880 !fill ntp and go to next event
253     endif
254    
255     FIMAGE=.false. !processing best track (not track image)
256     ibest=0 !best track among candidates
257     iimage=0 !track image
258     * ------------- select the best track -------------
259 pam-fi 1.9 c$$$ rchi2best=1000000000.
260     c$$$ do i=1,ntracks
261     c$$$ if(RCHI2_STORE(i).lt.rchi2best.and.
262     c$$$ $ RCHI2_STORE(i).gt.0)then
263     c$$$ ibest=i
264     c$$$ rchi2best=RCHI2_STORE(i)
265     c$$$ endif
266     c$$$ enddo
267     c$$$ if(ibest.eq.0)goto 880 !>> no good candidates
268    
269 pam-fi 1.15 * -------------------------------------------------------
270     * order track-candidates according to:
271     * 1st) decreasing n.points
272     * 2nd) increasing chi**2
273     * -------------------------------------------------------
274     rchi2best=1000000000.
275 pam-fi 1.20 ndofbest=0
276 mocchiut 1.1 do i=1,ntracks
277 pam-fi 1.20 ndof=0
278     do ii=1,nplanes
279     ndof=ndof
280     $ +int(xgood_store(ii,i))
281     $ +int(ygood_store(ii,i))
282     enddo
283     if(ndof.gt.ndofbest)then
284 pam-fi 1.15 ibest=i
285     rchi2best=RCHI2_STORE(i)
286 pam-fi 1.20 ndofbest=ndof
287     elseif(ndof.eq.ndofbest)then
288 pam-fi 1.15 if(RCHI2_STORE(i).lt.rchi2best.and.
289     $ RCHI2_STORE(i).gt.0)then
290 mocchiut 1.1 ibest=i
291     rchi2best=RCHI2_STORE(i)
292 pam-fi 1.20 ndofbest=ndof
293     endif
294 pam-fi 1.9 endif
295 mocchiut 1.1 enddo
296 pam-fi 1.15
297     c$$$ rchi2best=1000000000.
298     c$$$ ndofbest=0 !(1)
299     c$$$ do i=1,ntracks
300     c$$$ if(RCHI2_STORE(i).lt.rchi2best.and.
301     c$$$ $ RCHI2_STORE(i).gt.0)then
302     c$$$ ndof=0 !(1)
303     c$$$ do ii=1,nplanes !(1)
304     c$$$ ndof=ndof !(1)
305     c$$$ $ +int(xgood_store(ii,i)) !(1)
306     c$$$ $ +int(ygood_store(ii,i)) !(1)
307     c$$$ enddo !(1)
308     c$$$ if(ndof.ge.ndofbest)then !(1)
309     c$$$ ibest=i
310     c$$$ rchi2best=RCHI2_STORE(i)
311     c$$$ ndofbest=ndof !(1)
312     c$$$ endif !(1)
313     c$$$ endif
314     c$$$ enddo
315    
316 mocchiut 1.1 if(ibest.eq.0)goto 880 !>> no good candidates
317     *-------------------------------------------------------------------------------
318     * The best track candidate (ibest) is selected and a new fitting is performed.
319     * Previous to this, the track is refined by:
320     * - possibly adding new COUPLES or SINGLETS from the missing planes
321     * - evaluating the coordinates with improved PFAs
322     * ( angle-dependent ETA algorithms )
323     *-------------------------------------------------------------------------------
324    
325     1212 continue !<<<<< come here to fit track-image
326    
327     if(.not.FIMAGE)then !processing best candidate
328     icand=ibest
329     else !processing image
330     icand=iimage
331     iimage=0
332     endif
333     if(icand.eq.0)then
334 mocchiut 1.21 if(VERBOSE)then
335     print*,'HAI FATTO UN CASINO!!!!!! icand = ',icand
336     $ ,ibest,iimage
337     endif
338 mocchiut 1.1 return
339     endif
340    
341     * *-*-*-*-*-*-*-*-*-*-*-*-*-*-*
342     call refine_track(icand)
343     * *-*-*-*-*-*-*-*-*-*-*-*-*-*-*
344    
345     * **********************************************************
346     * ************************** FIT *** FIT *** FIT *** FIT ***
347     * **********************************************************
348 pam-fi 1.11 call guess()
349     do i=1,5
350     AL_GUESS(i)=AL(i)
351     enddo
352 pam-fi 1.17 c print*,'## guess: ',al
353 pam-fi 1.11
354 mocchiut 1.1 do i=1,5
355 pam-fi 1.3 AL(i)=dble(AL_STORE(i,icand))
356 mocchiut 1.1 enddo
357 pam-fi 1.11
358 pam-fi 1.3 IDCAND = icand !fitted track-candidate
359 mocchiut 1.1 ifail=0 !error flag in chi2 computation
360     jstep=0 !# minimization steps
361 pam-fi 1.9
362 pam-fi 1.8 iprint=0
363 pam-fi 1.11 c if(DEBUG)iprint=1
364 pam-fi 1.13 if(VERBOSE)iprint=1
365 pam-fi 1.16 if(DEBUG)iprint=2
366 pam-fi 1.8 call mini2(jstep,ifail,iprint)
367 mocchiut 1.1 if(ifail.ne.0) then
368 pam-fi 1.16 if(VERBOSE)then
369 mocchiut 1.1 print *,
370 pam-fi 1.11 $ '*** MINIMIZATION FAILURE *** (after refinement) '
371 mocchiut 1.1 $ ,iev
372 pam-fi 1.11
373 pam-fi 1.12 c$$$ print*,'guess: ',(al_guess(i),i=1,5)
374     c$$$ print*,'previous: ',(al_store(i,icand),i=1,5)
375     c$$$ print*,'result: ',(al(i),i=1,5)
376     c$$$ print*,'xgood ',xgood
377     c$$$ print*,'ygood ',ygood
378     c$$$ print*,'----------------------------------------------'
379 mocchiut 1.1 endif
380 pam-fi 1.11 c chi2=-chi2
381 mocchiut 1.1 endif
382    
383     if(DEBUG)then
384     print*,'----------------------------- improved track coord'
385     22222 format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
386     do ip=1,6
387     write(*,22222)ip,zm(ip),xm(ip),ym(ip)
388     $ ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)
389     $ ,xgood(ip),ygood(ip),resx(ip),resy(ip)
390     enddo
391     endif
392    
393     c rchi2=chi2/dble(ndof)
394     if(DEBUG)then
395     print*,' '
396     print*,'****** SELECTED TRACK *************'
397     print*,'# R. chi2 RIG'
398     print*,' --- ',chi2,' --- '
399     $ ,1./abs(AL(5))
400     print*,'***********************************'
401     endif
402     * **********************************************************
403     * ************************** FIT *** FIT *** FIT *** FIT ***
404     * **********************************************************
405    
406    
407     * ------------- search if the track has an IMAGE -------------
408     * ------------- (also this is stored ) -------------
409     if(FIMAGE)goto 122 !>>> jump! (this is already an image)
410     * now search for track-image, by comparing couples IDs
411     do i=1,ntracks
412     iimage=i
413     do ip=1,nplanes
414     if( CP_STORE(nplanes-ip+1,icand).ne.
415     $ -1*CP_STORE(nplanes-ip+1,i) )iimage=0
416     enddo
417     if( iimage.ne.0.and.
418     c $ RCHI2_STORE(i).le.CHI2MAX.and.
419     c $ RCHI2_STORE(i).gt.0.and.
420     $ .true.)then
421     if(DEBUG)print*,'Track candidate ',iimage
422     $ ,' >>> TRACK IMAGE >>> of'
423     $ ,ibest
424     goto 122 !image track found
425     endif
426     enddo
427     122 continue
428    
429     * --- and store the results --------------------------------
430     ntrk = ntrk + 1 !counter of found tracks
431     if(.not.FIMAGE
432     $ .and.iimage.eq.0) image(ntrk)= 0
433     if(.not.FIMAGE
434     $ .and.iimage.ne.0)image(ntrk)=ntrk+1 !this is the image of the next
435     if(FIMAGE) image(ntrk)=ntrk-1 !this is the image of the previous
436     call fill_level2_tracks(ntrk) !==> good2=.true.
437     c print*,'++++++++++ iimage,fimage,ntrk,image '
438     c $ ,iimage,fimage,ntrk,image(ntrk)
439    
440     if(ntrk.eq.NTRKMAX)then
441 pam-fi 1.5 if(verbose)
442 mocchiut 1.1 $ print*,
443     $ '** warning ** number of identified '//
444     $ 'tracks exceeds vector dimension '
445     $ ,'( ',NTRKMAX,' )'
446     cc good2=.false.
447     goto 880 !fill ntp and go to next event
448     endif
449     if(iimage.ne.0)then
450     FIMAGE=.true. !
451     goto 1212 !>>> fit image-track
452     endif
453    
454     * --- then remove selected clusters (ibest+iimage) from clouds ----
455     call clean_XYclouds(ibest,iflag)
456     if(iflag.eq.1)then !bad event
457     goto 880 !fill ntp and go to next event
458     endif
459    
460     * **********************************************************
461     * condition to start a new search
462     * **********************************************************
463     ixznew=0
464     do ixz=1,nclouds_xz
465     if(ptcloud_xz(ixz).ge.nptxz_min)ixznew=1
466     enddo
467     iyznew=0
468     do iyz=1,nclouds_yz
469     if(ptcloud_yz(iyz).ge.nptyz_min)iyznew=1
470     enddo
471    
472     if(ixznew.ne.0.and.
473     $ iyznew.ne.0.and.
474     $ rchi2best.le.CHI2MAX.and.
475     c $ rchi2best.lt.15..and.
476     $ .true.)then
477     if(DEBUG)then
478     print*,'***** NEW SEARCH ****'
479     endif
480     goto 11111 !try new search
481    
482     endif
483     * **********************************************
484    
485    
486    
487     880 return
488     end
489    
490    
491    
492     ************************************************************
493     ************************************************************
494     ************************************************************
495     ************************************************************
496     *
497     * This routine provides the coordinates (in cm) in the PAMELA reference system:
498     * - of the point associated with a COUPLE ---> (xPAM,yPAM,zPAM)
499     * - of the extremes of the segment
500     * associated with a SINGLET ---------------> (xPAM_A,yPAM_A,zPAM_A)
501     * ---> (xPAM_B,yPAM_B,zPAM_B)
502     *
503     * It also assigns the spatial resolution to the evaluated coordinates,
504     * as a function (in principle) of the multiplicity, the angle, the PFA etc...
505     *
506     *
507     * To call the routine you must pass the arguments:
508     * icx - ID of cluster x
509     * icy - ID of cluster y
510     * sensor - sensor (1,2)
511     * PFAx - Position Finding Algorithm in x (COG2,ETA2,...)
512     * PFAy - Position Finding Algorithm in y (COG2,ETA2,...)
513     * angx - Projected angle in x
514     * angy - Projected angle in y
515 pam-fi 1.18 * bfx - x-component of magnetci field
516     * bfy - y-component of magnetic field
517 mocchiut 1.1 *
518     * --------- COUPLES -------------------------------------------------------
519     * The couple defines a point in the space.
520     * The coordinates of the point are evaluated as follows:
521     * 1 - the corrected coordinates relative to the sensor are evaluated
522     * according to the chosen PFA --> (xi,yi,0)
523     * 2 - coordinates are rotated and traslated, according to the aligmnet
524     * parameters, and expressed in the reference system of the mechanical
525     * sensor --> (xrt,yrt,zrt)
526     * 3 - coordinates are finally converted to the PAMELA reference system
527     * --> (xPAM,yPAM,zPAM)
528     *
529     * --------- SINGLETS -------------------------------------------------------
530     * Since a coordinate is missing, the singlet defines not a point
531     * in the space but a segment AB (parallel to the strips).
532     * In this case the routine returns the coordinates in the PAMELA reference
533     * system of the two extremes A and B of the segment:
534     * --> (xPAM_A,yPAM_A,zPAM_A)
535     * --> (xPAM_B,yPAM_B,zPAM_B)
536     *
537     * ==========================================================
538     *
539     * The output of the routine is stored in the commons:
540     *
541     * double precision xPAM,yPAM,zPAM
542     * common/coord_xyz_PAM/xPAM,yPAM,zPAM
543     *
544     * double precision xPAM_A,yPAM_A,zPAM_A
545     * double precision xPAM_B,yPAM_B,zPAM_B
546     * common/coord_AB_PAM/xPAM_A,yPAM_A,zPAM_A,xPAM_B,yPAM_B,zPAM_B
547     *
548     * double precision resxPAM,resyPAM
549     * common/resolution_PAM/resxPAM,resyPAM
550     *
551     * (in file common_xyzPAM.f)
552     *
553     *
554    
555 pam-fi 1.18 subroutine xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
556 mocchiut 1.1
557    
558     include 'commontracker.f'
559 pam-fi 1.9 include 'level1.f'
560 mocchiut 1.1 include 'calib.f'
561     include 'common_align.f'
562     include 'common_mech.f'
563     include 'common_xyzPAM.f'
564    
565     integer icx,icy !X-Y cluster ID
566     integer sensor
567     integer viewx,viewy
568     character*4 PFAx,PFAy !PFA to be used
569 pam-fi 1.18 real ax,ay !X-Y geometric angle
570     real angx,angy !X-Y effective angle
571     real bfx,bfy !X-Y b-field components
572 mocchiut 1.1
573     real stripx,stripy
574    
575     double precision xrt,yrt,zrt
576     double precision xrt_A,yrt_A,zrt_A
577     double precision xrt_B,yrt_B,zrt_B
578    
579    
580     parameter (ndivx=30)
581 pam-fi 1.23
582    
583     c$$$ print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy
584 mocchiut 1.1
585     resxPAM = 0
586     resyPAM = 0
587    
588     xPAM = 0.
589     yPAM = 0.
590     zPAM = 0.
591     xPAM_A = 0.
592     yPAM_A = 0.
593     zPAM_A = 0.
594     xPAM_B = 0.
595     yPAM_B = 0.
596     zPAM_B = 0.
597 pam-fi 1.17 c print*,'## xyz_PAM: ',icx,icy,sensor,PFAx,PFAy,angx,angy
598 pam-fi 1.20
599 mocchiut 1.1 * -----------------
600     * CLUSTER X
601     * -----------------
602    
603     if(icx.ne.0)then
604 pam-fi 1.18
605 pam-fi 1.20 viewx = VIEW(icx)
606     nldx = nld(MAXS(icx),VIEW(icx))
607     nplx = npl(VIEW(icx))
608 pam-fi 1.18 resxPAM = RESXAV
609 pam-fi 1.20 stripx = float(MAXS(icx))
610 pam-fi 1.18 * --------------------------
611     * magnetic-field corrections
612     * --------------------------
613     angtemp = ax
614     bfytemp = bfy
615 pam-fi 1.22 * /////////////////////////////////
616     * AAAAHHHHHHHH!!!!!!!!!!!!!!!!!!!!!
617     * *grvzkkjsdgjhhhgngbn###>:(
618     * /////////////////////////////////
619     c if(nplx.eq.6) angtemp = -1. * ax
620     c if(nplx.eq.6) bfytemp = -1. * bfy
621     if(viewx.eq.12) angtemp = -1. * ax
622     if(viewx.eq.12) bfytemp = -1. * bfy
623 pam-fi 1.20 tgtemp = tan(angtemp*acos(-1.)/180.) + pmuH_h*bfytemp*0.00001
624     angx = 180.*atan(tgtemp)/acos(-1.)
625     stripx = stripx - 0.5*pmuH_h*bfytemp*0.00001*SiDimZ/pitchX
626     c$$$ print*,nplx,ax,bfy/10.
627 pam-fi 1.18 c$$$ print*,angx,0.5*pmuH_h*bfytemp*0.00001*SiDimZ/pitchX
628     c$$$ print*,'========================'
629 pam-fi 1.22 c$$$ if(bfy.ne.0.)print*,viewx,'-x- '
630     c$$$ $ ,bfy,-1*0.5*pmuH_h*bfytemp*0.00001*SiDimZ
631 pam-fi 1.18 * --------------------------
632    
633 pam-fi 1.20 c$$$ print*,'--- x-cl ---'
634     c$$$ istart = INDSTART(ICX)
635     c$$$ istop = TOTCLLENGTH
636     c$$$ if(icx.lt.NCLSTR1)istop=INDSTART(ICX+1)-1
637     c$$$ print*,(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)
638     c$$$ print*,(CLSIGNAL(i),i=istart,istop)
639     c$$$ print*,INDMAX(icx)
640     c$$$ print*,cog(4,icx)
641     c$$$ print*,fbad_cog(4,icx)
642    
643    
644 pam-fi 1.18 if(PFAx.eq.'COG1')then
645 pam-fi 1.20
646     stripx = stripx
647     resxPAM = 1e-4*pitchX/sqrt(12.)!!resxPAM
648    
649 mocchiut 1.1 elseif(PFAx.eq.'COG2')then
650 pam-fi 1.20
651     stripx = stripx + cog(2,icx)
652     resxPAM = risx_cog(abs(angx))!TEMPORANEO
653 mocchiut 1.1 resxPAM = resxPAM*fbad_cog(2,icx)
654 pam-fi 1.20
655 pam-fi 1.18 elseif(PFAx.eq.'COG3')then
656 pam-fi 1.20
657     stripx = stripx + cog(3,icx)
658     resxPAM = risx_cog(abs(angx))!TEMPORANEO
659 pam-fi 1.18 resxPAM = resxPAM*fbad_cog(3,icx)
660 pam-fi 1.20
661 pam-fi 1.18 elseif(PFAx.eq.'COG4')then
662 pam-fi 1.20
663     stripx = stripx + cog(4,icx)
664     resxPAM = risx_cog(abs(angx))!TEMPORANEO
665 pam-fi 1.18 resxPAM = resxPAM*fbad_cog(4,icx)
666 pam-fi 1.20
667 mocchiut 1.1 elseif(PFAx.eq.'ETA2')then
668 pam-fi 1.20
669     stripx = stripx + pfaeta2(icx,angx)
670     resxPAM = risx_eta2(abs(angx))
671     resxPAM = resxPAM*fbad_cog(2,icx)
672 mocchiut 1.1 if(DEBUG.and.fbad_cog(2,icx).ne.1)
673     $ print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)
674 pam-fi 1.20
675 pam-fi 1.18 elseif(PFAx.eq.'ETA3')then
676 pam-fi 1.20
677     stripx = stripx + pfaeta3(icx,angx)
678 pam-fi 1.18 resxPAM = risx_eta3(abs(angx))
679 pam-fi 1.20 resxPAM = resxPAM*fbad_cog(3,icx)
680 pam-fi 1.18 if(DEBUG.and.fbad_cog(3,icx).ne.1)
681     $ print*,'BAD icx >>> ',viewx,fbad_cog(3,icx)
682 pam-fi 1.20
683 pam-fi 1.18 elseif(PFAx.eq.'ETA4')then
684 pam-fi 1.20
685     stripx = stripx + pfaeta4(icx,angx)
686 pam-fi 1.18 resxPAM = risx_eta4(abs(angx))
687 pam-fi 1.20 resxPAM = resxPAM*fbad_cog(4,icx)
688 pam-fi 1.18 if(DEBUG.and.fbad_cog(4,icx).ne.1)
689     $ print*,'BAD icx >>> ',viewx,fbad_cog(4,icx)
690 pam-fi 1.20
691 pam-fi 1.18 elseif(PFAx.eq.'ETA')then
692 pam-fi 1.20
693     stripx = stripx + pfaeta(icx,angx)
694 pam-fi 1.24 c resxPAM = riseta(icx,angx)
695     resxPAM = riseta(viewx,angx)
696 pam-fi 1.20 resxPAM = resxPAM*fbad_eta(icx,angx)
697 pam-fi 1.18 if(DEBUG.and.fbad_cog(2,icx).ne.1)
698     $ print*,'BAD icx >>> ',viewx,fbad_cog(2,icx)
699 pam-fi 1.20
700 pam-fi 1.18 elseif(PFAx.eq.'COG')then
701 pam-fi 1.20
702     stripx = stripx + cog(0,icx)
703 pam-fi 1.18 resxPAM = risx_cog(abs(angx))
704     resxPAM = resxPAM*fbad_cog(0,icx)
705 pam-fi 1.20
706 mocchiut 1.1 else
707 mocchiut 1.21 if(DEBUG) print*,'*** Non valid p.f.a. (x) --> ',PFAx
708 mocchiut 1.1 endif
709    
710 pam-fi 1.20
711     * ======================================
712     * temporary patch for saturated clusters
713     * ======================================
714     if( nsatstrips(icx).gt.0 )then
715     stripx = stripx + cog(4,icx)
716     resxPAM = pitchX*1e-4/sqrt(12.)
717     cc=cog(4,icx)
718     c$$$ print*,icx,' *** ',cc
719     c$$$ print*,icx,' *** ',resxPAM
720     endif
721 pam-fi 1.18
722 mocchiut 1.1 endif
723    
724     * -----------------
725     * CLUSTER Y
726     * -----------------
727    
728     if(icy.ne.0)then
729 pam-fi 1.18
730 mocchiut 1.1 viewy = VIEW(icy)
731     nldy = nld(MAXS(icy),VIEW(icy))
732     nply = npl(VIEW(icy))
733 pam-fi 1.18 resyPAM = RESYAV
734     stripy = float(MAXS(icy))
735 mocchiut 1.1
736     if(icx.ne.0.and.(nply.ne.nplx.or.nldy.ne.nldx))then
737 mocchiut 1.21 if(DEBUG) then
738     print*,'xyz_PAM ***ERROR*** invalid cluster couple!!! '
739     $ ,icx,icy
740     endif
741 mocchiut 1.1 goto 100
742     endif
743 pam-fi 1.18 * --------------------------
744     * magnetic-field corrections
745     * --------------------------
746     tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001
747     angy = 180.*atan(tgtemp)/acos(-1.)
748     stripy = stripy + 0.5*pmuH_e*bfx*0.00001*SiDimZ/pitchY
749 pam-fi 1.22 c$$$ if(bfx.ne.0.)print*,viewy,'-y- '
750     c$$$ $ ,bfx,0.5*pmuH_e*bfx*0.00001*SiDimZ
751 pam-fi 1.18 * --------------------------
752 mocchiut 1.1
753 pam-fi 1.20 c$$$ print*,'--- y-cl ---'
754     c$$$ istart = INDSTART(ICY)
755     c$$$ istop = TOTCLLENGTH
756     c$$$ if(icy.lt.NCLSTR1)istop=INDSTART(ICY+1)-1
757     c$$$ print*,(CLSIGNAL(i)/CLSIGMA(i),i=istart,istop)
758     c$$$ print*,(CLSIGNAL(i),i=istart,istop)
759     c$$$ print*,INDMAX(icy)
760     c$$$ print*,cog(4,icy)
761     c$$$ print*,fbad_cog(4,icy)
762    
763     if(PFAy.eq.'COG1')then
764    
765     stripy = stripy
766     resyPAM = 1e-4*pitchY/sqrt(12.)!resyPAM
767    
768 mocchiut 1.1 elseif(PFAy.eq.'COG2')then
769 pam-fi 1.20
770     stripy = stripy + cog(2,icy)
771     resyPAM = risy_cog(abs(angy))!TEMPORANEO
772 mocchiut 1.1 resyPAM = resyPAM*fbad_cog(2,icy)
773 pam-fi 1.20
774 pam-fi 1.18 elseif(PFAy.eq.'COG3')then
775 pam-fi 1.20
776     stripy = stripy + cog(3,icy)
777     resyPAM = risy_cog(abs(angy))!TEMPORANEO
778 pam-fi 1.18 resyPAM = resyPAM*fbad_cog(3,icy)
779 pam-fi 1.20
780 pam-fi 1.18 elseif(PFAy.eq.'COG4')then
781 pam-fi 1.20
782     stripy = stripy + cog(4,icy)
783     resyPAM = risy_cog(abs(angy))!TEMPORANEO
784 pam-fi 1.18 resyPAM = resyPAM*fbad_cog(4,icy)
785 pam-fi 1.20
786 mocchiut 1.1 elseif(PFAy.eq.'ETA2')then
787 pam-fi 1.20
788     stripy = stripy + pfaeta2(icy,angy)
789     resyPAM = risy_eta2(abs(angy))
790 mocchiut 1.1 resyPAM = resyPAM*fbad_cog(2,icy)
791     if(DEBUG.and.fbad_cog(2,icy).ne.1)
792     $ print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)
793 pam-fi 1.20
794     elseif(PFAy.eq.'ETA3')then
795    
796     stripy = stripy + pfaeta3(icy,angy)
797     resyPAM = resyPAM*fbad_cog(3,icy)
798     if(DEBUG.and.fbad_cog(3,icy).ne.1)
799     $ print*,'BAD icy >>> ',viewy,fbad_cog(3,icy)
800    
801     elseif(PFAy.eq.'ETA4')then
802    
803     stripy = stripy + pfaeta4(icy,angy)
804     resyPAM = resyPAM*fbad_cog(4,icy)
805     if(DEBUG.and.fbad_cog(4,icy).ne.1)
806     $ print*,'BAD icy >>> ',viewy,fbad_cog(4,icy)
807    
808     elseif(PFAy.eq.'ETA')then
809    
810     stripy = stripy + pfaeta(icy,angy)
811 pam-fi 1.24 c resyPAM = riseta(icy,angy)
812     resyPAM = riseta(viewy,angy)
813 pam-fi 1.20 resyPAM = resyPAM*fbad_eta(icy,angy)
814     if(DEBUG.and.fbad_cog(2,icy).ne.1)
815     $ print*,'BAD icy >>> ',viewy,fbad_cog(2,icy)
816    
817 mocchiut 1.1 elseif(PFAy.eq.'COG')then
818 pam-fi 1.20
819     stripy = stripy + cog(0,icy)
820     resyPAM = risy_cog(abs(angy))
821 mocchiut 1.1 resyPAM = resyPAM*fbad_cog(0,icy)
822 pam-fi 1.20
823 mocchiut 1.1 else
824 mocchiut 1.21 if(DEBUG) print*,'*** Non valid p.f.a. (x) --> ',PFAx
825 mocchiut 1.1 endif
826    
827 pam-fi 1.20
828     * ======================================
829     * temporary patch for saturated clusters
830     * ======================================
831     if( nsatstrips(icy).gt.0 )then
832     stripy = stripy + cog(4,icy)
833     resyPAM = pitchY*1e-4/sqrt(12.)
834     cc=cog(4,icy)
835     c$$$ print*,icy,' *** ',cc
836     c$$$ print*,icy,' *** ',resyPAM
837     endif
838    
839    
840 mocchiut 1.1 endif
841    
842 pam-fi 1.23 c$$$ print*,'## stripx,stripy ',stripx,stripy
843 pam-fi 1.17
844 mocchiut 1.1 c===========================================================
845     C COUPLE
846     C===========================================================
847     if(icx.ne.0.and.icy.ne.0)then
848    
849     c------------------------------------------------------------------------
850     c (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
851     c------------------------------------------------------------------------
852 pam-fi 1.4 if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
853     $ .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
854 mocchiut 1.21 if(DEBUG) then
855     print*,'xyz_PAM (couple):',
856     $ ' WARNING: false X strip: strip ',stripx
857     endif
858 pam-fi 1.4 endif
859 mocchiut 1.1 xi = acoordsi(stripx,viewx)
860     yi = acoordsi(stripy,viewy)
861     zi = 0.
862    
863    
864     c------------------------------------------------------------------------
865     c (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
866     c------------------------------------------------------------------------
867     c N.B. I convert angles from microradiants to radiants
868    
869     xrt = xi
870     $ - omega(nplx,nldx,sensor)*yi
871     $ + gamma(nplx,nldx,sensor)*zi
872     $ + dx(nplx,nldx,sensor)
873    
874     yrt = omega(nplx,nldx,sensor)*xi
875     $ + yi
876     $ - beta(nplx,nldx,sensor)*zi
877     $ + dy(nplx,nldx,sensor)
878    
879     zrt = -gamma(nplx,nldx,sensor)*xi
880     $ + beta(nplx,nldx,sensor)*yi
881     $ + zi
882     $ + dz(nplx,nldx,sensor)
883    
884     c xrt = xi
885     c yrt = yi
886     c zrt = zi
887    
888     c------------------------------------------------------------------------
889     c (xPAM,yPAM,zPAM) = measured coordinates (in cm)
890     c in PAMELA reference system
891     c------------------------------------------------------------------------
892    
893     xPAM = dcoord(xrt,viewx,nldx,sensor) / 1.d4
894     yPAM = dcoord(yrt,viewy,nldy,sensor) / 1.d4
895     zPAM = ( zrt + z_mech_sensor(nplx,nldx,sensor)*1000. ) / 1.d4
896    
897     xPAM_A = 0.
898     yPAM_A = 0.
899     zPAM_A = 0.
900    
901     xPAM_B = 0.
902     yPAM_B = 0.
903     zPAM_B = 0.
904    
905     elseif(
906     $ (icx.ne.0.and.icy.eq.0).or.
907     $ (icx.eq.0.and.icy.ne.0).or.
908     $ .false.
909     $ )then
910    
911     c------------------------------------------------------------------------
912     c (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
913     c------------------------------------------------------------------------
914    
915     if(icy.ne.0)then
916     c===========================================================
917     C Y-SINGLET
918     C===========================================================
919     nplx = nply
920     nldx = nldy
921     viewx = viewy + 1
922    
923     yi = acoordsi(stripy,viewy)
924    
925     xi_A = edgeY_d - SiDimX/2
926     yi_A = yi
927     zi_A = 0.
928    
929     xi_B = SiDimX/2 - edgeY_u
930     yi_B = yi
931     zi_B = 0.
932    
933     c print*,'Y-cl ',icy,stripy,' --> ',yi
934     c print*,xi_A,' <--> ',xi_B
935    
936     elseif(icx.ne.0)then
937     c===========================================================
938     C X-SINGLET
939     C===========================================================
940    
941     nply = nplx
942     nldy = nldx
943     viewy = viewx - 1
944    
945 pam-fi 1.4 c print*,'X-singlet ',icx,nplx,nldx,viewx,stripx
946     c if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...
947     if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
948     $ .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
949 mocchiut 1.21 if(DEBUG) then
950     print*,'xyz_PAM (X-singlet):',
951     $ ' WARNING: false X strip: strip ',stripx
952     endif
953 pam-fi 1.4 endif
954 mocchiut 1.1 xi = acoordsi(stripx,viewx)
955    
956     xi_A = xi
957     yi_A = edgeX_d - SiDimY/2
958     zi_A = 0.
959    
960     xi_B = xi
961     yi_B = SiDimY/2 - edgeX_u
962     zi_B = 0.
963    
964     if(viewy.eq.11)then
965     yi = yi_A
966     yi_A = yi_B
967     yi_B = yi
968     endif
969    
970     c print*,'X-cl ',icx,stripx,' --> ',xi
971     c print*,yi_A,' <--> ',yi_B
972    
973     else
974 mocchiut 1.21 if(DEBUG) then
975     print *,'routine xyz_PAM ---> not properly used !!!'
976     print *,'icx = ',icx
977     print *,'icy = ',icy
978     endif
979 mocchiut 1.1 goto 100
980    
981     endif
982     c------------------------------------------------------------------------
983     c (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
984     c------------------------------------------------------------------------
985     c N.B. I convert angles from microradiants to radiants
986    
987     xrt_A = xi_A
988     $ - omega(nplx,nldx,sensor)*yi_A
989     $ + gamma(nplx,nldx,sensor)*zi_A
990     $ + dx(nplx,nldx,sensor)
991    
992     yrt_A = omega(nplx,nldx,sensor)*xi_A
993     $ + yi_A
994     $ - beta(nplx,nldx,sensor)*zi_A
995     $ + dy(nplx,nldx,sensor)
996    
997     zrt_A = -gamma(nplx,nldx,sensor)*xi_A
998     $ + beta(nplx,nldx,sensor)*yi_A
999     $ + zi_A
1000     $ + dz(nplx,nldx,sensor)
1001    
1002     xrt_B = xi_B
1003     $ - omega(nplx,nldx,sensor)*yi_B
1004     $ + gamma(nplx,nldx,sensor)*zi_B
1005     $ + dx(nplx,nldx,sensor)
1006    
1007     yrt_B = omega(nplx,nldx,sensor)*xi_B
1008     $ + yi_B
1009     $ - beta(nplx,nldx,sensor)*zi_B
1010     $ + dy(nplx,nldx,sensor)
1011    
1012     zrt_B = -gamma(nplx,nldx,sensor)*xi_B
1013     $ + beta(nplx,nldx,sensor)*yi_B
1014     $ + zi_B
1015     $ + dz(nplx,nldx,sensor)
1016    
1017    
1018     c xrt = xi
1019     c yrt = yi
1020     c zrt = zi
1021    
1022     c------------------------------------------------------------------------
1023     c (xPAM,yPAM,zPAM) = measured coordinates (in cm)
1024     c in PAMELA reference system
1025     c------------------------------------------------------------------------
1026    
1027     xPAM = 0.
1028     yPAM = 0.
1029     zPAM = 0.
1030    
1031     xPAM_A = dcoord(xrt_A,viewx,nldx,sensor) / 1.d4
1032     yPAM_A = dcoord(yrt_A,viewy,nldy,sensor) / 1.d4
1033     zPAM_A = ( zrt_A + z_mech_sensor(nplx,nldx,sensor)*1000.)/ 1.d4
1034    
1035     xPAM_B = dcoord(xrt_B,viewx,nldx,sensor) / 1.d4
1036     yPAM_B = dcoord(yrt_B,viewy,nldy,sensor) / 1.d4
1037     zPAM_B = ( zrt_B + z_mech_sensor(nplx,nldx,sensor)*1000.)/ 1.d4
1038    
1039    
1040     c print*,'A-(',xPAM_A,yPAM_A,') B-(',xPAM_B,yPAM_B,')'
1041    
1042     else
1043 mocchiut 1.21 if(DEBUG) then
1044     print *,'routine xyz_PAM ---> not properly used !!!'
1045     print *,'icx = ',icx
1046     print *,'icy = ',icy
1047     endif
1048 mocchiut 1.1 endif
1049    
1050 pam-fi 1.17
1051     c print*,'## xPAM,yPAM,zPAM ',xPAM,yPAM,zPAM
1052     c print*,'## xPAM_A,yPAM_A,zPAM_A ',xPAM_A,yPAM_A,zPAM_A
1053     c print*,'## xPAM_B,yPAM_B,zPAM_B ',xPAM_B,yPAM_B,zPAM_B
1054    
1055 mocchiut 1.1 100 continue
1056     end
1057    
1058 pam-fi 1.23 ************************************************************************
1059     * Call xyz_PAM subroutine with default PFA and fill the mini2 common.
1060     * (done to be called from c/c++)
1061     ************************************************************************
1062    
1063     subroutine xyzpam(ip,icx,icy,lad,sensor,ax,ay,bfx,bfy)
1064    
1065     include 'commontracker.f'
1066     include 'level1.f'
1067     include 'common_mini_2.f'
1068     include 'common_xyzPAM.f'
1069     include 'common_mech.f'
1070     include 'calib.f'
1071    
1072     * flag to chose PFA
1073     c$$$ character*10 PFA
1074     c$$$ common/FINALPFA/PFA
1075    
1076     integer icx,icy !X-Y cluster ID
1077     integer sensor
1078     character*4 PFAx,PFAy !PFA to be used
1079     real ax,ay !X-Y geometric angle
1080     real bfx,bfy !X-Y b-field components
1081    
1082     ipx=0
1083     ipy=0
1084    
1085     c$$$ PFAx = 'COG4'!PFA
1086     c$$$ PFAy = 'COG4'!PFA
1087    
1088     call idtoc(pfaid,PFAx)
1089     call idtoc(pfaid,PFAy)
1090    
1091     call xyz_PAM(icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy)
1092    
1093     c$$$ print*,icx,icy,sensor,PFAx,PFAy,ax,ay,bfx,bfy
1094    
1095     if(icx.ne.0.and.icy.ne.0)then
1096    
1097     ipx=npl(VIEW(icx))
1098     ipy=npl(VIEW(icy))
1099     if( (nplanes-ipx+1).ne.ip.or.(nplanes-ipy+1).ne.ip )
1100     $ print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1101     $ ,' does not belong to the correct plane: ',ip,ipx,ipy
1102    
1103     xgood(ip) = 1.
1104     ygood(ip) = 1.
1105     resx(ip) = resxPAM
1106     resy(ip) = resyPAM
1107    
1108     xm(ip) = xPAM
1109     ym(ip) = yPAM
1110     zm(ip) = zPAM
1111     xm_A(ip) = 0.
1112     ym_A(ip) = 0.
1113     xm_B(ip) = 0.
1114     ym_B(ip) = 0.
1115    
1116     c zv(ip) = zPAM
1117    
1118     elseif(icx.eq.0.and.icy.ne.0)then
1119    
1120     ipy=npl(VIEW(icy))
1121     if((nplanes-ipy+1).ne.ip)
1122     $ print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1123     $ ,' does not belong to the correct plane: ',ip,ipx,ipy
1124    
1125     xgood(ip) = 0.
1126     ygood(ip) = 1.
1127     resx(ip) = 1000.
1128     resy(ip) = resyPAM
1129    
1130     xm(ip) = -100.
1131     ym(ip) = -100.
1132     zm(ip) = (zPAM_A+zPAM_B)/2.
1133     xm_A(ip) = xPAM_A
1134     ym_A(ip) = yPAM_A
1135     xm_B(ip) = xPAM_B
1136     ym_B(ip) = yPAM_B
1137    
1138     c zv(ip) = (zPAM_A+zPAM_B)/2.
1139    
1140     elseif(icx.ne.0.and.icy.eq.0)then
1141    
1142     ipx=npl(VIEW(icx))
1143     if((nplanes-ipx+1).ne.ip)
1144     $ print*,'xyzpam: ***WARNING*** clusters ',icx,icy
1145     $ ,' does not belong to the correct plane: ',ip,ipx,ipy
1146    
1147     xgood(ip) = 1.
1148     ygood(ip) = 0.
1149     resx(ip) = resxPAM
1150     resy(ip) = 1000.
1151    
1152     xm(ip) = -100.
1153     ym(ip) = -100.
1154     zm(ip) = (zPAM_A+zPAM_B)/2.
1155     xm_A(ip) = xPAM_A
1156     ym_A(ip) = yPAM_A
1157     xm_B(ip) = xPAM_B
1158     ym_B(ip) = yPAM_B
1159    
1160     c zv(ip) = (zPAM_A+zPAM_B)/2.
1161    
1162     else
1163    
1164     il = 2
1165     if(lad.ne.0)il=lad
1166     is = 1
1167     if(sensor.ne.0)is=sensor
1168     c print*,nplanes-ip+1,il,is
1169    
1170     xgood(ip) = 0.
1171     ygood(ip) = 0.
1172     resx(ip) = 1000.
1173     resy(ip) = 1000.
1174    
1175     xm(ip) = -100.
1176     ym(ip) = -100.
1177     zm(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4
1178     xm_A(ip) = 0.
1179     ym_A(ip) = 0.
1180     xm_B(ip) = 0.
1181     ym_B(ip) = 0.
1182    
1183     c zv(ip) = z_mech_sensor(nplanes-ip+1,il,is)*1000./1.d4
1184    
1185     endif
1186    
1187     if(DEBUG)then
1188     c print*,'----------------------------- track coord'
1189     22222 format(i2,' * ',3f10.4,' --- ',4f10.4,' --- ',2f4.0,2f10.5)
1190     write(*,22222)ip,zm(ip),xm(ip),ym(ip)
1191     $ ,xm_A(ip),ym_A(ip),xm_B(ip),ym_B(ip)
1192     $ ,xgood(ip),ygood(ip),resx(ip),resy(ip)
1193     c$$$ print*,'-----------------------------'
1194     endif
1195     end
1196 mocchiut 1.1
1197     ********************************************************************************
1198     ********************************************************************************
1199     ********************************************************************************
1200     *
1201     * The function distance_to(XP,YP) should be used after
1202     * a call to the xyz_PAM routine and it evaluate the
1203     * NORMALIZED distance (PROJECTED on the XY plane) between
1204     * the point (XP,YP), argument of the function,
1205     * and:
1206     *
1207     * - the point (xPAM,yPAM,zPAM), in the case of a COUPLE
1208     * or
1209     * - the segment (xPAM_A,yPAM_A,zPAM_A)-(xPAM_B,yPAM_B,zPAM_B),
1210     * in the case of a SINGLET.
1211     *
1212     * ( The routine xyz_PAM fills the common defined in "common_xyzPAM.f",
1213     * which stores the coordinates of the couple/singlet )
1214     *
1215     ********************************************************************************
1216    
1217     real function distance_to(XPP,YPP)
1218    
1219     include 'common_xyzPAM.f'
1220    
1221     * -----------------------------------
1222     * it computes the normalized distance
1223     * ( i.e. distance/resolution )
1224     * -----------------------------------
1225    
1226     double precision distance,RE
1227     double precision BETA,ALFA,xmi,ymi
1228    
1229     * ----------------------
1230     if (
1231     + xPAM.eq.0.and.
1232     + yPAM.eq.0.and.
1233     + zPAM.eq.0.and.
1234     + xPAM_A.ne.0.and.
1235     + yPAM_A.ne.0.and.
1236     + zPAM_A.ne.0.and.
1237     + xPAM_B.ne.0.and.
1238     + yPAM_B.ne.0.and.
1239     + zPAM_B.ne.0.and.
1240     + .true.)then
1241     * -----------------------
1242     * DISTANCE TO --- SINGLET
1243     * -----------------------
1244     if(abs(sngl(xPAM_B-xPAM_A)).lt.abs(sngl(yPAM_B-yPAM_A)))then
1245     * |||---------- X CLUSTER
1246    
1247     BETA = (xPAM_B-xPAM_A)/(yPAM_B-yPAM_A)
1248     ALFA = xPAM_A - BETA * yPAM_A
1249    
1250     ymi = ( YPP + BETA*XPP - BETA*ALFA )/(1+BETA**2)
1251     if(ymi.lt.dmin1(yPAM_A,yPAM_B))ymi=dmin1(yPAM_A,yPAM_B)
1252     if(ymi.gt.dmax1(yPAM_A,yPAM_B))ymi=dmax1(yPAM_A,yPAM_B)
1253     xmi = ALFA + BETA * ymi
1254     RE = resxPAM
1255    
1256     else
1257     * |||---------- Y CLUSTER
1258    
1259     BETA = (yPAM_B-yPAM_A)/(xPAM_B-xPAM_A)
1260     ALFA = yPAM_A - BETA * xPAM_A
1261    
1262     xmi = ( XPP + BETA*YPP - BETA*ALFA )/(1+BETA**2)
1263     if(xmi.lt.dmin1(xPAM_A,xPAM_B))xmi=dmin1(xPAM_A,xPAM_B)
1264     if(xmi.gt.dmax1(xPAM_A,xPAM_B))xmi=dmax1(xPAM_A,xPAM_B)
1265     ymi = ALFA + BETA * xmi
1266     RE = resyPAM
1267    
1268     endif
1269    
1270     distance=
1271 pam-fi 1.20 $ ((xmi-XPP)**2+(ymi-YPP)**2)!QUIQUI
1272     cc $ ((xmi-XPP)**2+(ymi-YPP)**2)/RE**2
1273 mocchiut 1.1 distance=dsqrt(distance)
1274    
1275     c$$$ print*,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b
1276     c$$$ $ ,' --- distance_to --- ',xpp,ypp
1277     c$$$ print*,' resolution ',re
1278    
1279    
1280     * ----------------------
1281     elseif(
1282     + xPAM.ne.0.and.
1283     + yPAM.ne.0.and.
1284     + zPAM.ne.0.and.
1285     + xPAM_A.eq.0.and.
1286     + yPAM_A.eq.0.and.
1287     + zPAM_A.eq.0.and.
1288     + xPAM_B.eq.0.and.
1289     + yPAM_B.eq.0.and.
1290     + zPAM_B.eq.0.and.
1291     + .true.)then
1292     * ----------------------
1293     * DISTANCE TO --- COUPLE
1294     * ----------------------
1295    
1296     distance=
1297 pam-fi 1.20 $ ((xPAM-XPP))**2 !QUIQUI
1298     $ +
1299     $ ((yPAM-YPP))**2
1300     c$$$ $ ((xPAM-XPP)/resxPAM)**2
1301     c$$$ $ +
1302     c$$$ $ ((yPAM-YPP)/resyPAM)**2
1303 mocchiut 1.1 distance=dsqrt(distance)
1304    
1305     c$$$ print*,xPAM,yPAM,zPAM
1306     c$$$ $ ,' --- distance_to --- ',xpp,ypp
1307     c$$$ print*,' resolution ',resxPAM,resyPAM
1308    
1309     else
1310    
1311 mocchiut 1.21 c print*
1312     c $ ,' function distance_to ---> wrong usage!!!'
1313     c print*,' xPAM,yPAM,zPAM ',xPAM,yPAM,zPAM
1314     c print*,' xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b '
1315     c $ ,xPAM_A,yPAM_A,zPAM_A,xPAM_b,yPAM_b,zPAM_b
1316 mocchiut 1.1 endif
1317    
1318     distance_to = sngl(distance)
1319    
1320     return
1321     end
1322    
1323     ********************************************************************************
1324     ********************************************************************************
1325     ********************************************************************************
1326     ********************************************************************************
1327    
1328     subroutine whichsensor(nplPAM,xPAM,yPAM,ladder,sensor)
1329     * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
1330     * Given the plane (1-6 from BOTTOM to TOP!!) and the (xPAM,yPAM)
1331     * coordinates (in the PAMELA reference system), it returns
1332     * the ladder and the sensor which the point belongs to.
1333     *
1334     * The method to assign a point to a sensor consists in
1335     * - calculating the sum of the distances between the point
1336     * and the sensor edges
1337     * - requiring that it is less-equal than (SiDimX+SiDimY)
1338     *
1339     * NB -- SiDimX and SiDimY are not the dimentions of the SENSITIVE volume
1340     * but of the whole silicon sensor
1341     *
1342     * CONVENTION:
1343     * - sensor 1 is the one closest to the hybrid
1344     * - ladder 1 is the first to be read out (strips from 1 to 1024)
1345     *
1346     * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
1347     include 'commontracker.f'
1348     include 'common_align.f'
1349    
1350     integer ladder,sensor,viewx,viewy
1351     real c1(4),c2(4),c3(4)
1352     data c1/1.,0.,0.,1./
1353     data c2/1.,-1.,-1.,1./
1354     data c3/1.,1.,0.,0./
1355     real*8 yvvv,xvvv
1356     double precision xi,yi,zi
1357     double precision xrt,yrt,zrt
1358     real AA,BB
1359     real yvv(4),xvv(4)
1360    
1361     * tollerance to consider the track inside the sensitive area
1362     real ptoll
1363     data ptoll/150./ !um
1364    
1365     external nviewx,nviewy,acoordsi,dcoord
1366    
1367     nplpt = nplPAM !plane
1368     viewx = nviewx(nplpt)
1369     viewy = nviewy(nplpt)
1370    
1371     do il=1,nladders_view
1372     do is=1,2
1373    
1374     do iv=1,4 !loop on sensor vertexes
1375     stripx = (il-c1(iv))*1024 + c1(iv) + c2(iv)*3
1376     stripy = (il-c3(iv))*1024 + c3(iv)
1377     c------------------------------------------------------------------------
1378     c (xi,yi,zi) = mechanical coordinates in the silicon sensor frame
1379     c------------------------------------------------------------------------
1380 pam-fi 1.4 if(((mod(int(stripx+0.5)-1,1024)+1).le.3)
1381     $ .or.((mod(int(stripx+0.5)-1,1024)+1).ge.1022)) then !X has 1018 strips...
1382     c if((stripx.le.3).or.(stripx.ge.1022)) then !X has 1018 strips...
1383 mocchiut 1.21 c print*,'whichsensor: ',
1384     c $ ' WARNING: false X strip: strip ',stripx
1385 pam-fi 1.4 endif
1386 mocchiut 1.1 xi = acoordsi(stripx,viewx)
1387     yi = acoordsi(stripy,viewy)
1388     zi = 0.
1389     c------------------------------------------------------------------------
1390     c (xrt,yrt,zrt) = rototranslated coordinates in the silicon sensor frame
1391     c------------------------------------------------------------------------
1392     c N.B. I convert angles from microradiants to radiants
1393     xrt = xi
1394     $ - omega(nplpt,il,is)*yi
1395     $ + gamma(nplpt,il,is)*zi
1396     $ + dx(nplpt,il,is)
1397     yrt = omega(nplpt,il,is)*xi
1398     $ + yi
1399     $ - beta(nplpt,il,is)*zi
1400     $ + dy(nplpt,il,is)
1401     zrt = -gamma(nplpt,il,is)*xi
1402     $ + beta(nplpt,il,is)*yi
1403     $ + zi
1404     $ + dz(nplpt,il,is)
1405     c------------------------------------------------------------------------
1406     c measured coordinates (in cm) in PAMELA reference system
1407     c------------------------------------------------------------------------
1408     yvvv = dcoord(yrt,viewy,il,is) / 1.d4
1409     xvvv = dcoord(xrt,viewx,il,is) / 1.d4
1410    
1411     yvv(iv)=sngl(yvvv)
1412     xvv(iv)=sngl(xvvv)
1413     c print*,'LADDER ',il,' SENSOR ',is,' vertexes >> '
1414     c $ ,iv,xvv(iv),yvv(iv)
1415     enddo !end loop on sensor vertexes
1416    
1417     dtot=0.
1418     do iside=1,4,2 !loop on sensor edges X
1419     iv1=iside
1420     iv2=mod(iside,4)+1
1421     * straight line passing trhough two consecutive vertexes
1422     AA = (yvv(iv1)-yvv(iv2))/(xvv(iv1)-xvv(iv2))
1423     BB = yvv(iv1) - AA*xvv(iv1)
1424     * point along the straight line closer to the track
1425     xoo = (xPAM+AA*yPAM-AA*BB)/(1+AA**2)
1426     yoo = AA*xoo + BB
1427     * sum of the distances
1428     dtot = dtot +
1429     $ sqrt((xPAM-xoo)**2+(yPAM-yoo)**2)
1430     enddo !end loop on sensor edges
1431     do iside=2,4,2 !loop on sensor edges Y
1432     iv1=iside
1433     iv2=mod(iside,4)+1
1434     * straight line passing trhough two consecutive vertexes
1435     AA = (xvv(iv1)-xvv(iv2))/(yvv(iv1)-yvv(iv2))
1436     BB = xvv(iv1) - AA*yvv(iv1)
1437     * point along the straight line closer to the track
1438     yoo = (yPAM+AA*xPAM-AA*BB)/(1+AA**2)
1439     xoo = AA*yoo + BB
1440     * sum of the distances
1441     dtot = dtot +
1442     $ sqrt((xPAM-xoo)**2+(yPAM-yoo)**2)
1443     enddo !end loop on sensor edges
1444    
1445    
1446     * half-perimeter of sensitive area
1447     Perim =
1448     $ SiDimX - edgeX_l - edgeX_r
1449     $ +SiDimY - edgeY_l - edgeY_r
1450     Perim = (Perim + ptoll)/1.e4
1451     if(dtot.le.Perim)goto 100
1452    
1453    
1454     enddo
1455     enddo
1456    
1457     ladder = 0
1458     sensor = 0
1459     goto 200
1460    
1461     100 continue
1462     ladder = il
1463     sensor = is
1464    
1465    
1466     200 return
1467     end
1468    
1469    
1470    
1471     *************************************************************************
1472    
1473     subroutine reverse(v,n,temp) !invert the order of the components of v(n) vector
1474    
1475     implicit double precision (A-H,O-Z)
1476    
1477     dimension v(*)
1478     dimension temp(*)
1479     integer i,n
1480    
1481     do i=1,n
1482     temp(i)=v(n+1-i)
1483     enddo
1484    
1485     do i=1,n
1486     v(i)=temp(i)
1487     enddo
1488    
1489     return
1490     end
1491    
1492     *************************************************************************
1493     *************************************************************************
1494     *************************************************************************
1495     *************************************************************************
1496     *************************************************************************
1497     *************************************************************************
1498     *************************************************************************
1499     *************************************************************************
1500     *************************************************************************
1501     *************************************************************************
1502     *************************************************************************
1503     *************************************************************************
1504     *************************************************************************
1505     *************************************************************************
1506     *************************************************************************
1507     integer function ip_cp(id)
1508     *
1509     * given the couple id,
1510     * it returns the plane number
1511     *
1512     include 'commontracker.f'
1513 pam-fi 1.9 include 'level1.f'
1514 mocchiut 1.1 c include 'common_analysis.f'
1515     include 'common_momanhough.f'
1516    
1517     ip_cp=0
1518     ncpp=0
1519     do ip=1,nplanes
1520     ncpp=ncpp+ncp_plane(ip)
1521     if(ncpp.ge.abs(id))then
1522     ip_cp=ip
1523     goto 100
1524     endif
1525     enddo
1526     100 continue
1527     return
1528     end
1529    
1530    
1531     integer function is_cp(id)
1532     *
1533     * given the couple id,
1534     * it returns the sensor number
1535     *
1536     is_cp=0
1537     if(id.lt.0)is_cp=1
1538     if(id.gt.0)is_cp=2
1539 mocchiut 1.21 c if(id.eq.0)print*,'IS_CP ===> wrong couple id !!!'
1540 mocchiut 1.1
1541     return
1542     end
1543    
1544    
1545     integer function icp_cp(id)
1546     *
1547     * given the couple id,
1548     * it returns the id number ON THE PLANE
1549     *
1550     include 'commontracker.f'
1551 pam-fi 1.9 include 'level1.f'
1552 mocchiut 1.1 c include 'common_analysis.f'
1553     include 'common_momanhough.f'
1554    
1555     icp_cp=0
1556    
1557     ncpp=0
1558     do ip=1,nplanes
1559     ncppold=ncpp
1560     ncpp=ncpp+ncp_plane(ip)
1561     if(ncpp.ge.abs(id))then
1562     icp_cp=abs(id)-ncppold
1563     goto 100
1564     endif
1565     enddo
1566     100 continue
1567     return
1568     end
1569    
1570    
1571    
1572     integer function id_cp(ip,icp,is)
1573     *
1574     * given a plane, a couple and the sensor
1575     * it returns the absolute couple id
1576     * negative if sensor =1
1577     * positive if sensor =2
1578     *
1579     include 'commontracker.f'
1580 pam-fi 1.9 include 'level1.f'
1581 mocchiut 1.1 c include 'calib.f'
1582     c include 'level1.f'
1583     c include 'common_analysis.f'
1584     include 'common_momanhough.f'
1585    
1586     id_cp=0
1587    
1588     if(ip.gt.1)then
1589     do i=1,ip-1
1590     id_cp = id_cp + ncp_plane(i)
1591     enddo
1592     endif
1593    
1594     id_cp = id_cp + icp
1595    
1596     if(is.eq.1) id_cp = -id_cp
1597    
1598     return
1599     end
1600    
1601    
1602    
1603    
1604     *************************************************************************
1605     *************************************************************************
1606     *************************************************************************
1607     *************************************************************************
1608     *************************************************************************
1609     *************************************************************************
1610    
1611    
1612     ***************************************************
1613     * *
1614     * *
1615     * *
1616     * *
1617     * *
1618     * *
1619     **************************************************
1620    
1621     subroutine cl_to_couples(iflag)
1622    
1623     include 'commontracker.f'
1624 pam-fi 1.9 include 'level1.f'
1625 mocchiut 1.1 include 'common_momanhough.f'
1626 pam-fi 1.9 c include 'momanhough_init.f'
1627 mocchiut 1.1 include 'calib.f'
1628 pam-fi 1.9 c include 'level1.f'
1629 mocchiut 1.1
1630     * output flag
1631     * --------------
1632     * 0 = good event
1633     * 1 = bad event
1634     * --------------
1635     integer iflag
1636    
1637 pam-fi 1.6 integer badseed,badclx,badcly
1638 mocchiut 1.1
1639     * init variables
1640     ncp_tot=0
1641     do ip=1,nplanes
1642     do ico=1,ncouplemax
1643     clx(ip,ico)=0
1644     cly(ip,ico)=0
1645     enddo
1646     ncp_plane(ip)=0
1647     do icl=1,nclstrmax_level2
1648     cls(ip,icl)=1
1649     enddo
1650     ncls(ip)=0
1651     enddo
1652     do icl=1,nclstrmax_level2
1653 pam-fi 1.9 cl_single(icl) = 1
1654     cl_good(icl) = 0
1655     enddo
1656     do iv=1,nviews
1657     ncl_view(iv) = 0
1658     mask_view(iv) = 0 !all included
1659 mocchiut 1.1 enddo
1660    
1661 pam-fi 1.9 * count number of cluster per view
1662     do icl=1,nclstr1
1663     ncl_view(VIEW(icl)) = ncl_view(VIEW(icl)) + 1
1664     enddo
1665     * mask views with too many clusters
1666     do iv=1,nviews
1667 pam-fi 1.14 if( ncl_view(iv).gt. nclusterlimit)then
1668 pam-fi 1.9 mask_view(iv) = 1
1669 pam-fi 1.11 if(DEBUG)print*,' * WARNING * cl_to_couple: n.clusters > '
1670 pam-fi 1.14 $ ,nclusterlimit,' on view ', iv,' --> masked!'
1671 pam-fi 1.9 endif
1672     enddo
1673    
1674    
1675 mocchiut 1.1 * start association
1676     ncouples=0
1677     do icx=1,nclstr1 !loop on cluster (X)
1678     if(mod(VIEW(icx),2).eq.1)goto 10
1679    
1680     * ----------------------------------------------------
1681 pam-fi 1.9 * jump masked views (X VIEW)
1682     * ----------------------------------------------------
1683     if( mask_view(VIEW(icx)).ne.0 ) goto 10
1684     * ----------------------------------------------------
1685 mocchiut 1.1 * cut on charge (X VIEW)
1686 pam-fi 1.4 * ----------------------------------------------------
1687 pam-fi 1.18 if(sgnl(icx).lt.dedx_x_min)then
1688 mocchiut 1.1 cl_single(icx)=0
1689     goto 10
1690     endif
1691 pam-fi 1.4 * ----------------------------------------------------
1692 mocchiut 1.1 * cut BAD (X VIEW)
1693 pam-fi 1.4 * ----------------------------------------------------
1694 mocchiut 1.1 badseed=BAD(VIEW(icx),nvk(MAXS(icx)),nst(MAXS(icx)))
1695     ifirst=INDSTART(icx)
1696     if(icx.ne.nclstr1) then
1697     ilast=INDSTART(icx+1)-1
1698     else
1699     ilast=TOTCLLENGTH
1700     endif
1701 pam-fi 1.6 badclx=badseed
1702 mocchiut 1.1 do igood=-ngoodstr,ngoodstr
1703     ibad=1
1704     if((INDMAX(icx)+igood).gt.ifirst.and.
1705     $ (INDMAX(icx)+igood).lt.ilast.and.
1706     $ .true.)then
1707     ibad=BAD(VIEW(icx),
1708     $ nvk(MAXS(icx)+igood),
1709     $ nst(MAXS(icx)+igood))
1710     endif
1711 pam-fi 1.6 badclx=badclx*ibad
1712 mocchiut 1.1 enddo
1713 pam-fi 1.4 * ----------------------------------------------------
1714     * >>> eliminato il taglio sulle BAD <<<
1715     * ----------------------------------------------------
1716 mocchiut 1.1 c if(badcl.eq.0)then
1717     c cl_single(icx)=0
1718     c goto 10
1719     c endif
1720     * ----------------------------------------------------
1721    
1722     cl_good(icx)=1
1723     nplx=npl(VIEW(icx))
1724     nldx=nld(MAXS(icx),VIEW(icx))
1725    
1726     do icy=1,nclstr1 !loop on cluster (Y)
1727     if(mod(VIEW(icy),2).eq.0)goto 20
1728    
1729     * ----------------------------------------------------
1730 pam-fi 1.9 * jump masked views (Y VIEW)
1731     * ----------------------------------------------------
1732     if( mask_view(VIEW(icy)).ne.0 ) goto 20
1733    
1734     * ----------------------------------------------------
1735 mocchiut 1.1 * cut on charge (Y VIEW)
1736 pam-fi 1.4 * ----------------------------------------------------
1737 pam-fi 1.18 if(sgnl(icy).lt.dedx_y_min)then
1738 mocchiut 1.1 cl_single(icy)=0
1739     goto 20
1740     endif
1741 pam-fi 1.4 * ----------------------------------------------------
1742 mocchiut 1.1 * cut BAD (Y VIEW)
1743 pam-fi 1.4 * ----------------------------------------------------
1744 mocchiut 1.1 badseed=BAD(VIEW(icy),nvk(MAXS(icy)),nst(MAXS(icy)))
1745     ifirst=INDSTART(icy)
1746     if(icy.ne.nclstr1) then
1747     ilast=INDSTART(icy+1)-1
1748     else
1749     ilast=TOTCLLENGTH
1750     endif
1751 pam-fi 1.6 badcly=badseed
1752 mocchiut 1.1 do igood=-ngoodstr,ngoodstr
1753     ibad=1
1754     if((INDMAX(icy)+igood).gt.ifirst.and.
1755     $ (INDMAX(icy)+igood).lt.ilast.and.
1756     $ .true.)
1757     $ ibad=BAD(VIEW(icy),
1758     $ nvk(MAXS(icy)+igood),
1759     $ nst(MAXS(icy)+igood))
1760 pam-fi 1.6 badcly=badcly*ibad
1761 mocchiut 1.1 enddo
1762 pam-fi 1.4 * ----------------------------------------------------
1763     * >>> eliminato il taglio sulle BAD <<<
1764     * ----------------------------------------------------
1765 mocchiut 1.1 c if(badcl.eq.0)then
1766     c cl_single(icy)=0
1767     c goto 20
1768     c endif
1769     * ----------------------------------------------------
1770    
1771     cl_good(icy)=1
1772     nply=npl(VIEW(icy))
1773     nldy=nld(MAXS(icy),VIEW(icy))
1774    
1775     * ----------------------------------------------
1776     * CONDITION TO FORM A COUPLE
1777     * ----------------------------------------------
1778     * geometrical consistency (same plane and ladder)
1779     if(nply.eq.nplx.and.nldy.eq.nldx)then
1780     * charge correlation
1781 pam-fi 1.4 * (modified to be applied only below saturation... obviously)
1782    
1783 pam-fi 1.18 if( .not.(sgnl(icy).gt.chsaty.and.sgnl(icx).gt.chsatx)
1784 pam-fi 1.6 $ .and.
1785 pam-fi 1.18 $ .not.(sgnl(icy).lt.chmipy.and.sgnl(icx).lt.chmipx)
1786 pam-fi 1.6 $ .and.
1787     $ (badclx.eq.1.and.badcly.eq.1)
1788     $ .and.
1789     $ .true.)then
1790    
1791 pam-fi 1.18 ddd=(sgnl(icy)
1792     $ -kch(nplx,nldx)*sgnl(icx)-cch(nplx,nldx))
1793 pam-fi 1.6 ddd=ddd/sqrt(kch(nplx,nldx)**2+1)
1794    
1795     c cut = chcut * sch(nplx,nldx)
1796    
1797 pam-fi 1.18 sss=(kch(nplx,nldx)*sgnl(icy)+sgnl(icx)
1798 pam-fi 1.6 $ -kch(nplx,nldx)*cch(nplx,nldx))
1799     sss=sss/sqrt(kch(nplx,nldx)**2+1)
1800     cut = chcut * (16 + sss/50.)
1801    
1802     if(abs(ddd).gt.cut)then
1803     goto 20 !charge not consistent
1804     endif
1805     endif
1806 pam-fi 1.14
1807 pam-fi 1.15 if(ncp_plane(nplx).gt.ncouplemax)then
1808 pam-fi 1.5 if(verbose)print*,
1809     $ '** warning ** number of identified '//
1810     $ 'couples on plane ',nplx,
1811     $ 'exceeds vector dimention '
1812 pam-fi 1.14 $ ,'( ',ncouplemax,' ) --> masked!'
1813 pam-fi 1.10 mask_view(nviewx(nplx)) = 2
1814     mask_view(nviewy(nply)) = 2
1815 pam-fi 1.15 goto 10
1816 pam-fi 1.5 endif
1817 pam-fi 1.15
1818     * ------------------> COUPLE <------------------
1819     ncp_plane(nplx) = ncp_plane(nplx) + 1
1820     clx(nplx,ncp_plane(nplx))=icx
1821     cly(nply,ncp_plane(nplx))=icy
1822     cl_single(icx)=0
1823     cl_single(icy)=0
1824 pam-fi 1.14 * ----------------------------------------------
1825    
1826 mocchiut 1.1 endif
1827    
1828     20 continue
1829     enddo !end loop on clusters(Y)
1830    
1831     10 continue
1832     enddo !end loop on clusters(X)
1833    
1834    
1835     do icl=1,nclstr1
1836     if(cl_single(icl).eq.1)then
1837     ip=npl(VIEW(icl))
1838     ncls(ip)=ncls(ip)+1
1839     cls(ip,ncls(ip))=icl
1840     endif
1841     enddo
1842    
1843    
1844     if(DEBUG)then
1845     print*,'clusters ',nclstr1
1846     print*,'good ',(cl_good(i),i=1,nclstr1)
1847     print*,'singles ',(cl_single(i),i=1,nclstr1)
1848     print*,'couples per plane: ',(ncp_plane(ip),ip=1,nplanes)
1849     endif
1850    
1851     do ip=1,6
1852 pam-fi 1.10 ncp_tot = ncp_tot + ncp_plane(ip)
1853 mocchiut 1.1 enddo
1854    
1855     return
1856     end
1857    
1858     ***************************************************
1859     * *
1860     * *
1861     * *
1862     * *
1863     * *
1864     * *
1865     **************************************************
1866    
1867     subroutine cp_to_doubtrip(iflag)
1868    
1869     include 'commontracker.f'
1870 pam-fi 1.9 include 'level1.f'
1871 mocchiut 1.1 include 'common_momanhough.f'
1872     include 'common_xyzPAM.f'
1873     include 'common_mini_2.f'
1874     include 'calib.f'
1875    
1876    
1877     * output flag
1878     * --------------
1879     * 0 = good event
1880     * 1 = bad event
1881     * --------------
1882     integer iflag
1883    
1884    
1885     * -----------------------------
1886     * DOUBLETS/TRIPLETS coordinates
1887     c double precision xm1,ym1,zm1
1888     c double precision xm2,ym2,zm2
1889     c double precision xm3,ym3,zm3
1890    
1891     real xm1,ym1,zm1
1892     real xm2,ym2,zm2
1893     real xm3,ym3,zm3
1894     * -----------------------------
1895     * variable needed for tricircle:
1896     real xp(3),zp(3)!TRIPLETS coordinates, to find a circle
1897     EQUIVALENCE (xm1,xp(1))
1898     EQUIVALENCE (xm2,xp(2))
1899     EQUIVALENCE (xm3,xp(3))
1900     EQUIVALENCE (zm1,zp(1))
1901     EQUIVALENCE (zm2,zp(2))
1902     EQUIVALENCE (zm3,zp(3))
1903     real angp(3),resp(3),chi
1904     real xc,zc,radius
1905     * -----------------------------
1906    
1907    
1908 pam-fi 1.14 * --------------------------------------------
1909     * put a limit to the maximum number of couples
1910     * per plane, in order to apply hough transform
1911     * (couples recovered during track refinement)
1912     * --------------------------------------------
1913     do ip=1,nplanes
1914     if(ncp_plane(ip).gt.ncouplelimit)then
1915     mask_view(nviewx(ip)) = 8
1916     mask_view(nviewy(ip)) = 8
1917     endif
1918     enddo
1919    
1920 mocchiut 1.1
1921     ndblt=0 !number of doublets
1922     ntrpt=0 !number of triplets
1923    
1924     do ip1=1,(nplanes-1) !loop on planes - COPPIA 1
1925 pam-fi 1.14 if( mask_view(nviewx(ip1)).ne.0 .or.
1926     $ mask_view(nviewy(ip1)).ne.0 )goto 10 !skip plane
1927     do is1=1,2 !loop on sensors - COPPIA 1
1928 mocchiut 1.1 do icp1=1,ncp_plane(ip1) !loop on COPPIA 1
1929     icx1=clx(ip1,icp1)
1930     icy1=cly(ip1,icp1)
1931     c call xyz_PAM(icx1,icy1,is1,'COG2','COG2',0.,0.)!(1)
1932 pam-fi 1.18 c call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.) !(1)
1933     call xyz_PAM(icx1,icy1,is1,PFAdef,PFAdef,0.,0.,0.,0.)
1934 mocchiut 1.1 xm1=xPAM
1935     ym1=yPAM
1936     zm1=zPAM
1937     c print*,'***',is1,xm1,ym1,zm1
1938 pam-fi 1.14
1939 mocchiut 1.1 do ip2=(ip1+1),nplanes !loop on planes - COPPIA 2
1940 pam-fi 1.14 if( mask_view(nviewx(ip2)).ne.0 .or.
1941     $ mask_view(nviewy(ip2)).ne.0 )goto 20 !skip plane
1942 mocchiut 1.1 do is2=1,2 !loop on sensors -ndblt COPPIA 2
1943    
1944     do icp2=1,ncp_plane(ip2) !loop on COPPIA 2
1945     icx2=clx(ip2,icp2)
1946     icy2=cly(ip2,icp2)
1947     c call xyz_PAM
1948     c $ (icx2,icy2,is2,'COG2','COG2',0.,0.)!(1)
1949 pam-fi 1.18 c call xyz_PAM
1950     c $ (icx2,icy2,is2,PFAdef,PFAdef,0.,0.) !(1)
1951 mocchiut 1.1 call xyz_PAM
1952 pam-fi 1.18 $ (icx2,icy2,is2,PFAdef,PFAdef,0.,0.,0.,0.)
1953 mocchiut 1.1 xm2=xPAM
1954     ym2=yPAM
1955     zm2=zPAM
1956    
1957     * - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1958     * track parameters on Y VIEW
1959     * (2 couples needed)
1960     * - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1961     if(ndblt.eq.ndblt_max)then
1962 pam-fi 1.5 if(verbose)print*,
1963 mocchiut 1.1 $ '** warning ** number of identified '//
1964     $ 'doublets exceeds vector dimention '
1965     $ ,'( ',ndblt_max,' )'
1966     c good2=.false.
1967     c goto 880 !fill ntp and go to next event
1968 pam-fi 1.10 do iv=1,12
1969     mask_view(iv) = 3
1970     enddo
1971 mocchiut 1.1 iflag=1
1972     return
1973     endif
1974     ndblt = ndblt + 1
1975     * store doublet info
1976     cpyz1(ndblt)=id_cp(ip1,icp1,is1)
1977     cpyz2(ndblt)=id_cp(ip2,icp2,is2)
1978     * tg(th_yz)
1979     alfayz2(ndblt)=(ym1-ym2)/(zm1-zm2)
1980     * y0 (cm)
1981     alfayz1(ndblt)=alfayz2(ndblt)*(zini-zm1)+ym1
1982    
1983     **** -----------------------------------------------****
1984     **** reject non phisical couples ****
1985     **** -----------------------------------------------****
1986     if(
1987     $ abs(alfayz2(ndblt)).gt.alfyz2_max
1988     $ .or.
1989     $ abs(alfayz1(ndblt)).gt.alfyz1_max
1990     $ )ndblt = ndblt-1
1991    
1992     c$$$ if(iev.eq.33)then
1993     c$$$ print*,'********* ',ndblt,' -- ',icp1,icp2,is1,is2
1994     c$$$ $ ,' || ',icx1,icy1,icx2,icy2
1995     c$$$ $ ,' || ',xm1,ym1,xm2,ym2
1996     c$$$ $ ,' || ',alfayz2(ndblt),alfayz1(ndblt)
1997     c$$$ endif
1998     c$$$
1999     * - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2000     * track parameters on Y VIEW - end
2001     * - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2002    
2003    
2004 pam-fi 1.14 if(ip2.eq.nplanes)goto 31 !no possible combination with 3 couples
2005    
2006 mocchiut 1.1 do ip3=(ip2+1),nplanes !loop on planes - COPPIA 3
2007 pam-fi 1.14 if( mask_view(nviewx(ip3)).ne.0 .or.
2008     $ mask_view(nviewy(ip3)).ne.0 )goto 30 !skip plane
2009 mocchiut 1.1 do is3=1,2 !loop on sensors - COPPIA 3
2010    
2011     do icp3=1,ncp_plane(ip3) !loop on COPPIA 3
2012     icx3=clx(ip3,icp3)
2013     icy3=cly(ip3,icp3)
2014     c call xyz_PAM
2015     c $ (icx3,icy3,is3,'COG2','COG2',0.,0.)!(1)
2016 pam-fi 1.18 c call xyz_PAM
2017     c $ (icx3,icy3,is3,PFAdef,PFAdef,0.,0.) !(1)
2018 mocchiut 1.1 call xyz_PAM
2019 pam-fi 1.18 $ (icx3,icy3,is3,PFAdef,PFAdef
2020     $ ,0.,0.,0.,0.)
2021 mocchiut 1.1 xm3=xPAM
2022     ym3=yPAM
2023     zm3=zPAM
2024     * find the circle passing through the three points
2025     call tricircle(3,xp,zp,angp,resp,chi
2026     $ ,xc,zc,radius,iflag)
2027     c print*,xc,zc,radius
2028     * the circle must intersect the reference plane
2029     if(
2030     c $ (xc.le.-1.*xclimit.or.
2031     c $ xc.ge.xclimit).and.
2032     $ radius**2.ge.(ZINI-zc)**2.and.
2033     $ iflag.eq.0.and.
2034     $ .true.)then
2035    
2036     * - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2037     * track parameters on X VIEW
2038     * (3 couples needed)
2039     * - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2040     if(ntrpt.eq.ntrpt_max)then
2041 pam-fi 1.5 if(verbose)print*,
2042 mocchiut 1.1 $ '** warning ** number of identified '//
2043     $ 'triplets exceeds vector dimention '
2044     $ ,'( ',ntrpt_max,' )'
2045     c good2=.false.
2046     c goto 880 !fill ntp and go to next event
2047 pam-fi 1.10 do iv=1,nviews
2048     mask_view(iv) = 4
2049     enddo
2050 mocchiut 1.1 iflag=1
2051     return
2052     endif
2053     ntrpt = ntrpt +1
2054     * store triplet info
2055     cpxz1(ntrpt)=id_cp(ip1,icp1,is1)
2056     cpxz2(ntrpt)=id_cp(ip2,icp2,is2)
2057     cpxz3(ntrpt)=id_cp(ip3,icp3,is3)
2058    
2059     if(xc.lt.0)then
2060     *************POSITIVE DEFLECTION
2061     alfaxz1(ntrpt) = xc+sqrt(radius**2-(ZINI-zc)**2)
2062     alfaxz2(ntrpt) = (ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2063     alfaxz3(ntrpt) = 1/radius
2064     else
2065     *************NEGATIVE DEFLECTION
2066     alfaxz1(ntrpt) = xc-sqrt(radius**2-(ZINI-zc)**2)
2067     alfaxz2(ntrpt) = -(ZINI-zc)/sqrt(radius**2-(ZINI-zc)**2)
2068     alfaxz3(ntrpt) = -1/radius
2069     endif
2070    
2071     **** -----------------------------------------------****
2072     **** reject non phisical triplets ****
2073     **** -----------------------------------------------****
2074     if(
2075     $ abs(alfaxz2(ntrpt)).gt.alfxz2_max
2076     $ .or.
2077     $ abs(alfaxz1(ntrpt)).gt.alfxz1_max
2078     $ )ntrpt = ntrpt-1
2079    
2080    
2081     c print*,alfaxz1(ntrpt),alfaxz2(ntrpt),alfaxz3(ntrpt)
2082     * - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2083     * track parameters on X VIEW - end
2084     * - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2085     endif
2086     enddo !end loop on COPPIA 3
2087     enddo !end loop on sensors - COPPIA 3
2088 pam-fi 1.14 30 continue
2089 mocchiut 1.1 enddo !end loop on planes - COPPIA 3
2090 pam-fi 1.14 31 continue
2091 mocchiut 1.1
2092     1 enddo !end loop on COPPIA 2
2093     enddo !end loop on sensors - COPPIA 2
2094 pam-fi 1.14 20 continue
2095 mocchiut 1.1 enddo !end loop on planes - COPPIA 2
2096    
2097     enddo !end loop on COPPIA1
2098     enddo !end loop on sensors - COPPIA 1
2099 pam-fi 1.14 10 continue
2100 mocchiut 1.1 enddo !end loop on planes - COPPIA 1
2101    
2102     if(DEBUG)then
2103     print*,'--- doublets ',ndblt
2104     print*,'--- triplets ',ntrpt
2105     endif
2106    
2107     c goto 880 !ntp fill
2108    
2109    
2110     return
2111     end
2112    
2113    
2114    
2115     ***************************************************
2116     * *
2117     * *
2118     * *
2119     * *
2120     * *
2121     * *
2122     **************************************************
2123    
2124     subroutine doub_to_YZcloud(iflag)
2125    
2126     include 'commontracker.f'
2127 pam-fi 1.9 include 'level1.f'
2128 mocchiut 1.1 include 'common_momanhough.f'
2129 pam-fi 1.9 c include 'momanhough_init.f'
2130 mocchiut 1.1
2131    
2132     * output flag
2133     * --------------
2134     * 0 = good event
2135     * 1 = bad event
2136     * --------------
2137     integer iflag
2138    
2139     integer db_used(ndblt_max)
2140     integer db_temp(ndblt_max)
2141     integer db_all(ndblt_max) !stores db ID in each cloud
2142    
2143     integer hit_plane(nplanes)
2144    
2145     * mask for used couples
2146     integer cp_useds1(ncouplemaxtot) ! sensor 1
2147     integer cp_useds2(ncouplemaxtot) ! sensor 2
2148    
2149    
2150     *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2151     * classification of DOUBLETS
2152     * according to distance in parameter space
2153     * (cloud = group of points (doublets) in parameter space)
2154     *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2155     do idb=1,ndblt
2156     db_used(idb)=0
2157     enddo
2158    
2159     distance=0
2160     nclouds_yz=0 !number of clouds
2161     npt_tot=0
2162 pam-fi 1.9 nloop=0
2163     90 continue
2164 mocchiut 1.1 do idb1=1,ndblt !loop (1) on DOUBLETS
2165     if(db_used(idb1).eq.1)goto 2228 !db already included in a cloud
2166    
2167     c print*,'--------------'
2168     c print*,'** ',idb1,' **'
2169    
2170     do icp=1,ncp_tot
2171     cp_useds1(icp)=0 !init
2172     cp_useds2(icp)=0 !init
2173     enddo
2174     do idb=1,ndblt
2175     db_all(idb)=0
2176     enddo
2177     if(cpyz1(idb1).gt.0)cp_useds2(cpyz1(idb1))=1
2178     if(cpyz1(idb1).lt.0)cp_useds1(-cpyz1(idb1))=1
2179     if(cpyz2(idb1).gt.0)cp_useds2(cpyz2(idb1))=1
2180     if(cpyz2(idb1).lt.0)cp_useds1(-cpyz2(idb1))=1
2181     temp1 = alfayz1(idb1)
2182     temp2 = alfayz2(idb1)
2183     npt=1 !counter of points in the cloud
2184    
2185     db_all(npt) = idb1
2186    
2187     nptloop=1
2188     db_temp(1)=idb1
2189    
2190     88 continue
2191    
2192     npv=0 !# new points inlcuded
2193     do iloop=1,nptloop
2194     idbref=db_temp(iloop) !local point of reference
2195     ccccc if(db_used(idbref).eq.1)goto 1188 !next
2196    
2197     do idb2=1,ndblt !loop (2) on DOUBLETS
2198     if(idb2.eq.idbref)goto 1118 !next doublet
2199     if(db_used(idb2).eq.1)goto 1118
2200    
2201    
2202     * doublet distance in parameter space
2203     distance=
2204     $ ((alfayz1(idbref)-alfayz1(idb2))/Dalfayz1)**2
2205     $ +((alfayz2(idbref)-alfayz2(idb2))/Dalfayz2)**2
2206     distance = sqrt(distance)
2207    
2208     c$$$ if(iev.eq.33)then
2209     c$$$ if(distance.lt.100)
2210     c$$$ $ print*,'********* ',idb1,idbref,idb2,distance
2211     c$$$ if(distance.lt.100)
2212     c$$$ $ print*,'********* ',alfayz1(idbref),alfayz1(idb2)
2213     c$$$ $ ,alfayz2(idbref),alfayz2(idb2)
2214     c$$$ endif
2215     if(distance.lt.cutdistyz)then
2216    
2217     c print*,idb1,idb2,distance,' cloud ',nclouds_yz
2218     if(cpyz1(idb2).gt.0)cp_useds2(cpyz1(idb2))=1
2219     if(cpyz1(idb2).lt.0)cp_useds1(-cpyz1(idb2))=1
2220     if(cpyz2(idb2).gt.0)cp_useds2(cpyz2(idb2))=1
2221     if(cpyz2(idb2).lt.0)cp_useds1(-cpyz2(idb2))=1
2222     npt = npt + 1 !counter of points in the cloud
2223    
2224     npv = npv +1
2225     db_temp(npv) = idb2
2226     db_used(idbref) = 1
2227     db_used(idb2) = 1
2228    
2229     db_all(npt) = idb2
2230    
2231     temp1 = temp1 + alfayz1(idb2)
2232     temp2 = temp2 + alfayz2(idb2)
2233     c print*,'* idbref,idb2 ',idbref,idb2
2234     endif
2235    
2236     1118 continue
2237     enddo !end loop (2) on DOUBLETS
2238    
2239     1188 continue
2240     enddo !end loop on... bo?
2241    
2242     nptloop=npv
2243     if(nptloop.ne.0)goto 88
2244    
2245     * ------------------------------------------
2246     * stores the cloud only if
2247     * 1) it includes a minimum number of REAL couples
2248     * 1bis) it inlcudes a minimum number of doublets
2249     * 2) it is not already stored
2250     * ------------------------------------------
2251     do ip=1,nplanes
2252     hit_plane(ip)=0
2253     enddo
2254     ncpused=0
2255     do icp=1,ncp_tot
2256     if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then
2257     ncpused=ncpused+1
2258     ip=ip_cp(icp)
2259     hit_plane(ip)=1
2260     endif
2261     enddo
2262     nplused=0
2263     do ip=1,nplanes
2264     nplused=nplused+ hit_plane(ip)
2265     enddo
2266     c print*,'>>>> ',ncpused,npt,nplused
2267 pam-fi 1.9 c if(ncpused.lt.ncpyz_min)goto 2228 !next doublet
2268 mocchiut 1.1 if(npt.lt.nptyz_min)goto 2228 !next doublet
2269     if(nplused.lt.nplyz_min)goto 2228 !next doublet
2270    
2271     * ~~~~~~~~~~~~~~~~~
2272     * >>> NEW CLOUD <<<
2273    
2274     if(nclouds_yz.ge.ncloyz_max)then
2275 pam-fi 1.5 if(verbose)print*,
2276 mocchiut 1.1 $ '** warning ** number of identified '//
2277     $ 'YZ clouds exceeds vector dimention '
2278     $ ,'( ',ncloyz_max,' )'
2279     c good2=.false.
2280     c goto 880 !fill ntp and go to next event
2281 pam-fi 1.10 do iv=1,nviews
2282     mask_view(iv) = 5
2283     enddo
2284 mocchiut 1.1 iflag=1
2285     return
2286     endif
2287    
2288     nclouds_yz = nclouds_yz + 1 !increase counter
2289     alfayz1_av(nclouds_yz) = temp1/npt !store average parameter
2290     alfayz2_av(nclouds_yz) = temp2/npt ! "
2291     do icp=1,ncp_tot
2292     cpcloud_yz(nclouds_yz,icp)=
2293     $ cp_useds1(icp)+2*cp_useds2(icp) !store cp info
2294     enddo
2295     ptcloud_yz(nclouds_yz)=npt
2296     c ptcloud_yz_nt(nclouds_yz)=npt
2297     do ipt=1,npt
2298     db_cloud(npt_tot+ipt) = db_all(ipt)
2299     c print*,'>> ',ipt,db_all(ipt)
2300     enddo
2301     npt_tot=npt_tot+npt
2302     if(DEBUG)then
2303     print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'
2304     print*,'>>>> cloud ',nclouds_yz,' --- ',npt,' points'
2305     print*,'- alfayz1 ',alfayz1_av(nclouds_yz)
2306     print*,'- alfayz2 ',alfayz2_av(nclouds_yz)
2307     print*,'cp_useds1 ',(cp_useds1(icp),icp=1,ncp_tot)
2308     print*,'cp_useds2 ',(cp_useds2(icp),icp=1,ncp_tot)
2309     print*,'hit_plane ',(hit_plane(ip),ip=1,nplanes)
2310     c$$$ print*,'nt-uple: ptcloud_yz(',nclouds_yz,') = '
2311     c$$$ $ ,ptcloud_yz(nclouds_yz)
2312     c$$$ print*,'nt-uple: db_cloud(...) = '
2313     c$$$ $ ,(db_cloud(iii),iii=npt_tot-npt+1,npt_tot)
2314     endif
2315     * >>> NEW CLOUD <<<
2316     * ~~~~~~~~~~~~~~~~~
2317     2228 continue
2318     enddo !end loop (1) on DOUBLETS
2319    
2320    
2321 pam-fi 1.9 if(nloop.lt.nstepy)then
2322     cutdistyz = cutdistyz+cutystep
2323     nloop = nloop+1
2324     goto 90
2325     endif
2326    
2327 mocchiut 1.1 if(DEBUG)then
2328     print*,'---------------------- '
2329     print*,'Y-Z total clouds ',nclouds_yz
2330     print*,' '
2331     endif
2332    
2333    
2334     return
2335     end
2336    
2337    
2338    
2339    
2340    
2341     ***************************************************
2342     * *
2343     * *
2344     * *
2345     * *
2346     * *
2347     * *
2348     **************************************************
2349    
2350     subroutine trip_to_XZcloud(iflag)
2351    
2352     include 'commontracker.f'
2353 pam-fi 1.9 include 'level1.f'
2354 mocchiut 1.1 include 'common_momanhough.f'
2355 pam-fi 1.9 c include 'momanhough_init.f'
2356 mocchiut 1.1
2357    
2358     * output flag
2359     * --------------
2360     * 0 = good event
2361     * 1 = bad event
2362     * --------------
2363     integer iflag
2364    
2365     integer tr_used(ntrpt_max)
2366     integer tr_temp(ntrpt_max)
2367     integer tr_incl(ntrpt_max)
2368     integer tr_all(ntrpt_max) !stores tr ID in each cloud
2369    
2370     integer hit_plane(nplanes)
2371    
2372     * mask for used couples
2373     integer cp_useds1(ncouplemaxtot) ! sensor 1
2374     integer cp_useds2(ncouplemaxtot) ! sensor 2
2375    
2376     *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2377     * classification of TRIPLETS
2378     * according to distance in parameter space
2379     *~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2380     do itr=1,ntrpt
2381     tr_used(itr)=0
2382     enddo
2383    
2384     distance=0
2385     nclouds_xz=0 !number of clouds
2386     npt_tot=0 !total number of selected triplets
2387 pam-fi 1.9 nloop=0
2388     91 continue
2389 mocchiut 1.1 do itr1=1,ntrpt !loop (1) on TRIPLETS
2390     if(tr_used(itr1).eq.1)goto 22288 !already included in a cloud
2391     c print*,'--------------'
2392     c print*,'** ',itr1,' **'
2393    
2394     do icp=1,ncp_tot
2395     cp_useds1(icp)=0
2396     cp_useds2(icp)=0
2397     enddo
2398     do itr=1,ntrpt
2399     tr_all(itr)=0 !list of included triplets
2400     enddo
2401     if(cpxz1(itr1).gt.0)cp_useds2(cpxz1(itr1))=1
2402     if(cpxz1(itr1).lt.0)cp_useds1(-cpxz1(itr1))=1
2403     if(cpxz2(itr1).gt.0)cp_useds2(cpxz2(itr1))=1
2404     if(cpxz2(itr1).lt.0)cp_useds1(-cpxz2(itr1))=1
2405     if(cpxz3(itr1).gt.0)cp_useds2(cpxz3(itr1))=1
2406     if(cpxz3(itr1).lt.0)cp_useds1(-cpxz3(itr1))=1
2407     temp1 = alfaxz1(itr1)
2408     temp2 = alfaxz2(itr1)
2409     temp3 = alfaxz3(itr1)
2410     npt=1 !counter of points in the cloud
2411    
2412     tr_all(npt) = itr1
2413    
2414     nptloop=1
2415     c tr_temp(1)=itr1
2416     tr_incl(1)=itr1
2417    
2418     8881 continue
2419    
2420     npv=0 !# new points inlcuded
2421     do iloop=1,nptloop
2422     itrref=tr_incl(iloop) !local point of reference
2423     do itr2=1,ntrpt !loop (2) on TRIPLETS
2424     if(itr2.eq.itr1)goto 11188 !next triplet
2425     if(tr_used(itr2).eq.1)goto 11188 !next triplet
2426     * triplet distance in parameter space
2427     * solo i due parametri spaziali per il momemnto
2428     distance=
2429     $ ((alfaxz1(itrref)-alfaxz1(itr2))/Dalfaxz1)**2
2430     $ +((alfaxz2(itrref)-alfaxz2(itr2))/Dalfaxz2)**2
2431     distance = sqrt(distance)
2432    
2433     if(distance.lt.cutdistxz)then
2434     c print*,idb1,idb2,distance,' cloud ',nclouds_yz
2435     if(cpxz1(itr2).gt.0)cp_useds2(cpxz1(itr2))=1
2436     if(cpxz1(itr2).lt.0)cp_useds1(-cpxz1(itr2))=1
2437     if(cpxz2(itr2).gt.0)cp_useds2(cpxz2(itr2))=1
2438     if(cpxz2(itr2).lt.0)cp_useds1(-cpxz2(itr2))=1
2439     if(cpxz3(itr2).gt.0)cp_useds2(cpxz3(itr2))=1
2440     if(cpxz3(itr2).lt.0)cp_useds1(-cpxz3(itr2))=1
2441     npt = npt + 1 !counter of points in the cloud
2442    
2443     npv = npv +1
2444     tr_temp(npv) = itr2
2445     tr_used(itrref) = 1
2446     tr_used(itr2) = 1
2447    
2448     tr_all(npt) = itr2
2449    
2450     temp1 = temp1 + alfaxz1(itr2)
2451     temp2 = temp2 + alfaxz2(itr2)
2452     temp3 = temp3 + alfaxz3(itr2)
2453     c print*,'* itrref,itr2 ',itrref,itr2,distance
2454     endif
2455    
2456     11188 continue
2457     enddo !end loop (2) on TRIPLETS
2458    
2459     11888 continue
2460     enddo !end loop on... bo?
2461    
2462     nptloop=npv
2463     do i=1,npv
2464     tr_incl(i)=tr_temp(i)
2465     enddo
2466     if(nptloop.ne.0)goto 8881
2467    
2468     * ------------------------------------------
2469     * stores the cloud only if
2470     * 1) it includes a minimum number of REAL couples
2471     * 1bis)
2472     * 2) it is not already stored
2473     * ------------------------------------------
2474     c print*,'check cp_used'
2475     do ip=1,nplanes
2476     hit_plane(ip)=0
2477     enddo
2478     ncpused=0
2479     do icp=1,ncp_tot
2480     if(cp_useds1(icp).ne.0.or.cp_useds2(icp).ne.0)then
2481     ncpused=ncpused+1
2482     ip=ip_cp(icp)
2483     hit_plane(ip)=1
2484     endif
2485     enddo
2486     nplused=0
2487     do ip=1,nplanes
2488     nplused=nplused+ hit_plane(ip)
2489     enddo
2490 pam-fi 1.9 c if(ncpused.lt.ncpxz_min)goto 22288 !next triplet
2491 mocchiut 1.1 if(npt.lt.nptxz_min)goto 22288 !next triplet
2492 pam-fi 1.20 if(nplused.lt.nplxz_min)goto 22288 !next triplet
2493 mocchiut 1.1
2494     * ~~~~~~~~~~~~~~~~~
2495     * >>> NEW CLOUD <<<
2496     if(nclouds_xz.ge.ncloxz_max)then
2497 pam-fi 1.5 if(verbose)print*,
2498 mocchiut 1.1 $ '** warning ** number of identified '//
2499     $ 'XZ clouds exceeds vector dimention '
2500     $ ,'( ',ncloxz_max,' )'
2501     c good2=.false.
2502     c goto 880 !fill ntp and go to next event
2503 pam-fi 1.10 do iv=1,nviews
2504     mask_view(iv) = 6
2505     enddo
2506 mocchiut 1.1 iflag=1
2507     return
2508     endif
2509     nclouds_xz = nclouds_xz + 1 !increase counter
2510     alfaxz1_av(nclouds_xz) = temp1/npt !store average parameter
2511     alfaxz2_av(nclouds_xz) = temp2/npt ! "
2512     alfaxz3_av(nclouds_xz) = temp3/npt ! "
2513     do icp=1,ncp_tot
2514     cpcloud_xz(nclouds_xz,icp)=
2515     $ cp_useds1(icp)+2*cp_useds2(icp) !store cp info
2516     enddo
2517     ptcloud_xz(nclouds_xz)=npt
2518     do ipt=1,npt
2519     tr_cloud(npt_tot+ipt) = tr_all(ipt)
2520     enddo
2521     npt_tot=npt_tot+npt
2522    
2523     if(DEBUG)then
2524     print*,'-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~-~'
2525     print*,'>>>> cloud ',nclouds_xz,' --- ',npt,' points'
2526     print*,'- alfaxz1 ',alfaxz1_av(nclouds_xz)
2527     print*,'- alfaxz2 ',alfaxz2_av(nclouds_xz)
2528     print*,'- alfaxz3 ',alfaxz3_av(nclouds_xz)
2529     print*,'cp_useds1 ',(cp_useds1(icp),icp=1,ncp_tot)
2530     print*,'cp_useds2 ',(cp_useds2(icp),icp=1,ncp_tot)
2531     print*,'hit_plane ',(hit_plane(ip),ip=1,nplanes)
2532     c$$$ print*,'nt-uple: ptcloud_xz(',nclouds_xz,') = '
2533     c$$$ $ ,ptcloud_xz(nclouds_xz)
2534     c$$$ print*,'nt-uple: tr_cloud(...) = '
2535     c$$$ $ ,(tr_cloud(iii),iii=npt_tot-npt+1,npt_tot)
2536     endif
2537     * >>> NEW CLOUD <<<
2538     * ~~~~~~~~~~~~~~~~~
2539     22288 continue
2540     enddo !end loop (1) on DOUBLETS
2541 pam-fi 1.9
2542     if(nloop.lt.nstepx)then
2543     cutdistxz=cutdistxz+cutxstep
2544     nloop=nloop+1
2545     goto 91
2546     endif
2547    
2548 mocchiut 1.1 if(DEBUG)then
2549     print*,'---------------------- '
2550     print*,'X-Z total clouds ',nclouds_xz
2551     print*,' '
2552     endif
2553    
2554    
2555     return
2556     end
2557    
2558    
2559     ***************************************************
2560     * *
2561     * *
2562     * *
2563     * *
2564     * *
2565     * *
2566     **************************************************
2567    
2568     subroutine clouds_to_ctrack(iflag)
2569    
2570     include 'commontracker.f'
2571 pam-fi 1.9 include 'level1.f'
2572 mocchiut 1.1 include 'common_momanhough.f'
2573     include 'common_xyzPAM.f'
2574     include 'common_mini_2.f'
2575     include 'common_mech.f'
2576 pam-fi 1.20
2577 mocchiut 1.1
2578    
2579     * output flag
2580     * --------------
2581     * 0 = good event
2582     * 1 = bad event
2583     * --------------
2584     integer iflag
2585    
2586     * -----------------------------------------------------------
2587     * mask to store (locally) the couples included
2588     * in the intersection bewteen a XZ and YZ cloud
2589     integer cpintersec(ncouplemaxtot)
2590     * -----------------------------------------------------------
2591     * list of matching couples in the combination
2592     * between a XZ and YZ cloud
2593 pam-fi 1.9 integer cp_match(nplanes,2*ncouplemax)
2594 mocchiut 1.1 integer ncp_match(nplanes)
2595     * -----------------------------------------------------------
2596     integer hit_plane(nplanes)
2597     * -----------------------------------------------------------
2598     * variables for track fitting
2599     double precision AL_INI(5)
2600 pam-fi 1.11 c double precision tath
2601 mocchiut 1.1 * -----------------------------------------------------------
2602     c real fitz(nplanes) !z coordinates of the planes in cm
2603    
2604    
2605    
2606     ntracks=0 !counter of track candidates
2607    
2608     do iyz=1,nclouds_yz !loop on YZ couds
2609     do ixz=1,nclouds_xz !loop on XZ couds
2610    
2611     * --------------------------------------------------
2612     * check of consistency of the clouds
2613     * ---> required a minimum number of matching couples
2614     * the track fit will be performed on the INTERSECTION
2615     * of the two clouds
2616     * --------------------------------------------------
2617     do ip=1,nplanes
2618     hit_plane(ip)=0
2619     ncp_match(ip)=0
2620     do icpp=1,ncouplemax
2621     cp_match(ip,icpp)=0 !init couple list
2622     enddo
2623     enddo
2624     ncp_ok=0
2625     do icp=1,ncp_tot !loop on couples
2626     * get info on
2627     cpintersec(icp)=min(
2628     $ cpcloud_yz(iyz,icp),
2629     $ cpcloud_xz(ixz,icp))
2630     if(
2631     $ (cpcloud_yz(iyz,icp).eq.1.and.cpcloud_xz(ixz,icp).eq.2).or.
2632     $ (cpcloud_yz(iyz,icp).eq.2.and.cpcloud_xz(ixz,icp).eq.1).or.
2633     $ .false.)cpintersec(icp)=0
2634     if(cpintersec(icp).ne.0)then
2635     ncp_ok=ncp_ok+1
2636    
2637     ip=ip_cp(icp)
2638     hit_plane(ip)=1
2639     if(cpintersec(icp).eq.1)then
2640     * 1) only the couple image in sensor 1 matches
2641     id=-icp
2642     ncp_match(ip)=ncp_match(ip)+1
2643     cp_match(ip,ncp_match(ip))=id
2644     elseif(cpintersec(icp).eq.2)then
2645     * 2) only the couple image in sensor 2 matches
2646     id=icp
2647     ncp_match(ip)=ncp_match(ip)+1
2648     cp_match(ip,ncp_match(ip))=id
2649     else
2650     * 3) both couple images match
2651     id=icp
2652     do is=1,2
2653     id=-id
2654     ncp_match(ip)=ncp_match(ip)+1
2655     cp_match(ip,ncp_match(ip))=id
2656     enddo
2657     endif
2658     endif !end matching condition
2659     enddo !end loop on couples
2660    
2661     nplused=0
2662     do ip=1,nplanes
2663     nplused=nplused+ hit_plane(ip)
2664     enddo
2665    
2666 pam-fi 1.15 c if(nplused.lt.nplxz_min)goto 888 !next doublet
2667     if(nplused.lt.nplyz_min)goto 888 !next doublet
2668 mocchiut 1.1 if(ncp_ok.lt.ncpok)goto 888 !next cloud
2669    
2670     if(DEBUG)then
2671     print*,'Combination ',iyz,ixz
2672     $ ,' db ',ptcloud_yz(iyz)
2673     $ ,' tr ',ptcloud_xz(ixz)
2674     $ ,' -----> # matching couples ',ncp_ok
2675     endif
2676     c$$$ print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'
2677     c$$$ print*,'Configurazione cluster XZ'
2678     c$$$ print*,'1 -- ',(clx(1,i),i=1,ncp_plane(1))
2679     c$$$ print*,'2 -- ',(clx(2,i),i=1,ncp_plane(1))
2680     c$$$ print*,'3 -- ',(clx(3,i),i=1,ncp_plane(1))
2681     c$$$ print*,'4 -- ',(clx(4,i),i=1,ncp_plane(1))
2682     c$$$ print*,'5 -- ',(clx(5,i),i=1,ncp_plane(1))
2683     c$$$ print*,'6 -- ',(clx(6,i),i=1,ncp_plane(1))
2684     c$$$ print*,'Configurazione cluster YZ'
2685     c$$$ print*,'1 -- ',(cly(1,i),i=1,ncp_plane(1))
2686     c$$$ print*,'2 -- ',(cly(2,i),i=1,ncp_plane(1))
2687     c$$$ print*,'3 -- ',(cly(3,i),i=1,ncp_plane(1))
2688     c$$$ print*,'4 -- ',(cly(4,i),i=1,ncp_plane(1))
2689     c$$$ print*,'5 -- ',(cly(5,i),i=1,ncp_plane(1))
2690     c$$$ print*,'6 -- ',(cly(6,i),i=1,ncp_plane(1))
2691     c$$$ print*,'~~~~~~~~~~~~~~~~~~~~~~~~~'
2692    
2693     * -------> INITIAL GUESS <-------
2694 pam-fi 1.11 cccc SBAGLIATO
2695     c$$$ AL_INI(1) = dreal(alfaxz1_av(ixz))
2696     c$$$ AL_INI(2) = dreal(alfayz1_av(iyz))
2697     c$$$ AL_INI(4) = PIGR + datan(dreal(alfayz2_av(iyz))
2698     c$$$ $ /dreal(alfaxz2_av(ixz)))
2699     c$$$ tath = -dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))
2700     c$$$ AL_INI(3) = tath/sqrt(1+tath**2)
2701     c$$$ AL_INI(5) = (1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.
2702     cccc GIUSTO (ma si sua guess())
2703     c$$$ AL_INI(1) = dreal(alfaxz1_av(ixz))
2704     c$$$ AL_INI(2) = dreal(alfayz1_av(iyz))
2705     c$$$ tath = -dreal(alfaxz2_av(ixz))/dcos(AL_INI(4))
2706     c$$$ AL_INI(3) = tath/sqrt(1+tath**2)
2707     c$$$ IF(alfaxz2_av(ixz).NE.0)THEN
2708     c$$$ AL_INI(4) = PIGR + datan(dreal(alfayz2_av(iyz))
2709     c$$$ $ /dreal(alfaxz2_av(ixz)))
2710     c$$$ ELSE
2711     c$$$ AL_INI(4) = acos(-1.)/2
2712     c$$$ IF(alfayz2_av(iyz).LT.0)AL_INI(4) = AL_INI(4)+acos(-1.)
2713     c$$$ ENDIF
2714     c$$$ IF(alfaxz2_av(ixz).LT.0)AL_INI(4)= acos(-1.)+ AL_INI(4)
2715     c$$$ AL_INI(4) = -acos(-1.) + AL_INI(4) !from incidence direction to tracking rs
2716     c$$$
2717     c$$$ AL_INI(5) = (1.e2*alfaxz3_av(ixz))/(0.3*0.43) !0.
2718     c$$$
2719     c$$$ if(AL_INI(5).gt.defmax)goto 888 !next cloud
2720    
2721 mocchiut 1.1 if(DEBUG)then
2722     print*,'1 >>> ',(cp_match(6,i),i=1,ncp_match(6))
2723     print*,'2 >>> ',(cp_match(5,i),i=1,ncp_match(5))
2724     print*,'3 >>> ',(cp_match(4,i),i=1,ncp_match(4))
2725     print*,'4 >>> ',(cp_match(3,i),i=1,ncp_match(3))
2726     print*,'5 >>> ',(cp_match(2,i),i=1,ncp_match(2))
2727     print*,'6 >>> ',(cp_match(1,i),i=1,ncp_match(1))
2728     endif
2729    
2730     do icp1=1,max(1,ncp_match(1))
2731     hit_plane(1)=icp1
2732     if(ncp_match(1).eq.0)hit_plane(1)=0 !-icp1
2733    
2734     do icp2=1,max(1,ncp_match(2))
2735     hit_plane(2)=icp2
2736     if(ncp_match(2).eq.0)hit_plane(2)=0 !-icp2
2737    
2738     do icp3=1,max(1,ncp_match(3))
2739     hit_plane(3)=icp3
2740     if(ncp_match(3).eq.0)hit_plane(3)=0 !-icp3
2741    
2742     do icp4=1,max(1,ncp_match(4))
2743     hit_plane(4)=icp4
2744     if(ncp_match(4).eq.0)hit_plane(4)=0 !-icp4
2745    
2746     do icp5=1,max(1,ncp_match(5))
2747     hit_plane(5)=icp5
2748     if(ncp_match(5).eq.0)hit_plane(5)=0 !-icp5
2749    
2750     do icp6=1,max(1,ncp_match(6))
2751     hit_plane(6)=icp6
2752     if(ncp_match(6).eq.0)hit_plane(6)=0 !-icp6
2753    
2754    
2755     call track_init !init TRACK common
2756    
2757     do ip=1,nplanes !loop on planes
2758     if(hit_plane(ip).ne.0)then
2759     id=cp_match(ip,hit_plane(ip))
2760     is=is_cp(id)
2761     icp=icp_cp(id)
2762     if(ip_cp(id).ne.ip)
2763     $ print*,'OKKIO!!'
2764     $ ,'id ',id,is,icp
2765     $ ,ip_cp(id),ip
2766     icx=clx(ip,icp)
2767     icy=cly(ip,icp)
2768     * *************************
2769     c call xyz_PAM(icx,icy,is,
2770     c $ 'COG2','COG2',0.,0.)
2771 pam-fi 1.18 c call xyz_PAM(icx,icy,is, !(1)
2772     c $ PFAdef,PFAdef,0.,0.) !(1)
2773 mocchiut 1.1 call xyz_PAM(icx,icy,is, !(1)
2774 pam-fi 1.18 $ PFAdef,PFAdef,0.,0.,0.,0.)
2775 mocchiut 1.1 * *************************
2776     * -----------------------------
2777     xgood(nplanes-ip+1)=1.
2778     ygood(nplanes-ip+1)=1.
2779     xm(nplanes-ip+1)=xPAM
2780     ym(nplanes-ip+1)=yPAM
2781     zm(nplanes-ip+1)=zPAM
2782     resx(nplanes-ip+1)=resxPAM
2783     resy(nplanes-ip+1)=resyPAM
2784     * -----------------------------
2785     endif
2786     enddo !end loop on planes
2787     * **********************************************************
2788     * ************************** FIT *** FIT *** FIT *** FIT ***
2789     * **********************************************************
2790 pam-fi 1.11 cccc scommentare se si usa al_ini della nuvola
2791     c$$$ do i=1,5
2792     c$$$ AL(i)=AL_INI(i)
2793     c$$$ enddo
2794     call guess()
2795 mocchiut 1.1 do i=1,5
2796 pam-fi 1.11 AL_INI(i)=AL(i)
2797 mocchiut 1.1 enddo
2798     ifail=0 !error flag in chi^2 computation
2799     jstep=0 !number of minimization steps
2800 pam-fi 1.8 iprint=0
2801 pam-fi 1.11 c if(DEBUG)iprint=1
2802 pam-fi 1.16 if(DEBUG)iprint=2
2803 pam-fi 1.8 call mini2(jstep,ifail,iprint)
2804 mocchiut 1.1 if(ifail.ne.0) then
2805     if(DEBUG)then
2806     print *,
2807     $ '*** MINIMIZATION FAILURE *** '
2808 pam-fi 1.11 $ //'(clouds_to_ctrack)'
2809     print*,'initial guess: '
2810    
2811     print*,'AL_INI(1) = ',AL_INI(1)
2812     print*,'AL_INI(2) = ',AL_INI(2)
2813     print*,'AL_INI(3) = ',AL_INI(3)
2814     print*,'AL_INI(4) = ',AL_INI(4)
2815     print*,'AL_INI(5) = ',AL_INI(5)
2816 mocchiut 1.1 endif
2817 pam-fi 1.11 c chi2=-chi2
2818 mocchiut 1.1 endif
2819     * **********************************************************
2820     * ************************** FIT *** FIT *** FIT *** FIT ***
2821     * **********************************************************
2822    
2823     if(chi2.le.0.)goto 666
2824    
2825     * --------------------------
2826     * STORE candidate TRACK INFO
2827     * --------------------------
2828     if(ntracks.eq.NTRACKSMAX)then
2829    
2830 pam-fi 1.5 if(verbose)print*,
2831 mocchiut 1.1 $ '** warning ** number of candidate tracks '//
2832     $ ' exceeds vector dimension '
2833     $ ,'( ',NTRACKSMAX,' )'
2834     c good2=.false.
2835     c goto 880 !fill ntp and go to next event
2836 pam-fi 1.10 do iv=1,nviews
2837     mask_view(iv) = 7
2838     enddo
2839 mocchiut 1.1 iflag=1
2840     return
2841     endif
2842    
2843     ntracks = ntracks + 1
2844    
2845     do ip=1,nplanes
2846 pam-fi 1.20
2847 mocchiut 1.1 XV_STORE(ip,ntracks)=sngl(xv(ip))
2848     YV_STORE(ip,ntracks)=sngl(yv(ip))
2849     ZV_STORE(ip,ntracks)=sngl(zv(ip))
2850     XM_STORE(ip,ntracks)=sngl(xm(ip))
2851     YM_STORE(ip,ntracks)=sngl(ym(ip))
2852     ZM_STORE(ip,ntracks)=sngl(zm(ip))
2853     RESX_STORE(ip,ntracks)=sngl(resx(ip))
2854     RESY_STORE(ip,ntracks)=sngl(resy(ip))
2855     XV_STORE(ip,ntracks)=sngl(xv(ip))
2856     YV_STORE(ip,ntracks)=sngl(yv(ip))
2857     ZV_STORE(ip,ntracks)=sngl(zv(ip))
2858     AXV_STORE(ip,ntracks)=sngl(axv(ip))
2859     AYV_STORE(ip,ntracks)=sngl(ayv(ip))
2860     XGOOD_STORE(ip,ntracks)=sngl(xgood(ip))
2861     YGOOD_STORE(ip,ntracks)=sngl(ygood(ip))
2862     if(hit_plane(ip).ne.0)then
2863     CP_STORE(nplanes-ip+1,ntracks)=
2864     $ cp_match(ip,hit_plane(ip))
2865 pam-fi 1.20 SENSOR_STORE(nplanes-ip+1,ntracks)
2866     $ = is_cp(cp_match(ip,hit_plane(ip)))
2867     LADDER_STORE(nplanes-ip+1,ntracks)
2868     $ = LADDER(
2869     $ clx(ip,icp_cp(
2870     $ cp_match(ip,hit_plane(ip)
2871     $ ))));
2872 mocchiut 1.1 else
2873     CP_STORE(nplanes-ip+1,ntracks)=0
2874 pam-fi 1.20 SENSOR_STORE(nplanes-ip+1,ntracks)=0
2875     LADDER_STORE(nplanes-ip+1,ntracks)=0
2876 mocchiut 1.1 endif
2877 pam-fi 1.20 BX_STORE(nplanes-ip+1,ntracks)=0!I dont need it now
2878     BY_STORE(nplanes-ip+1,ntracks)=0!I dont need it now
2879 mocchiut 1.1 CLS_STORE(nplanes-ip+1,ntracks)=0
2880     do i=1,5
2881     AL_STORE(i,ntracks)=sngl(AL(i))
2882     enddo
2883     enddo
2884    
2885     RCHI2_STORE(ntracks)=chi2
2886    
2887     * --------------------------------
2888     * STORE candidate TRACK INFO - end
2889     * --------------------------------
2890    
2891     666 continue
2892     enddo !end loop on cp in plane 6
2893     enddo !end loop on cp in plane 5
2894     enddo !end loop on cp in plane 4
2895     enddo !end loop on cp in plane 3
2896     enddo !end loop on cp in plane 2
2897     enddo !end loop on cp in plane 1
2898    
2899     888 continue
2900     enddo !end loop on XZ couds
2901     enddo !end loop on YZ couds
2902    
2903     if(ntracks.eq.0)then
2904     iflag=1
2905     return
2906     endif
2907    
2908 pam-fi 1.20 c$$$ if(DEBUG)then
2909     c$$$ print*,'****** TRACK CANDIDATES ***********'
2910     c$$$ print*,'# R. chi2 RIG'
2911     c$$$ do i=1,ntracks
2912     c$$$ print*,i,' --- ',rchi2_store(i),' --- '
2913     c$$$ $ ,1./abs(AL_STORE(5,i))
2914     c$$$ enddo
2915     c$$$ print*,'***********************************'
2916     c$$$ endif
2917 mocchiut 1.1 if(DEBUG)then
2918 pam-fi 1.20 print*,'****** TRACK CANDIDATES *****************'
2919     print*,'# R. chi2 RIG ndof'
2920     do i=1,ntracks
2921     ndof=0 !(1)
2922     do ii=1,nplanes !(1)
2923     ndof=ndof !(1)
2924     $ +int(xgood_store(ii,i)) !(1)
2925     $ +int(ygood_store(ii,i)) !(1)
2926     enddo !(1)
2927     print*,i,' --- ',rchi2_store(i),' --- '
2928     $ ,1./abs(AL_STORE(5,i)),' --- ',ndof
2929     enddo
2930     print*,'*****************************************'
2931 mocchiut 1.1 endif
2932    
2933    
2934     return
2935     end
2936    
2937    
2938     ***************************************************
2939     * *
2940     * *
2941     * *
2942     * *
2943     * *
2944     * *
2945     **************************************************
2946    
2947     subroutine refine_track(ibest)
2948    
2949    
2950     include 'commontracker.f'
2951 pam-fi 1.9 include 'level1.f'
2952 mocchiut 1.1 include 'common_momanhough.f'
2953     include 'common_xyzPAM.f'
2954     include 'common_mini_2.f'
2955     include 'common_mech.f'
2956     include 'calib.f'
2957    
2958     * flag to chose PFA
2959     character*10 PFA
2960     common/FINALPFA/PFA
2961    
2962 pam-fi 1.20 real k(6)
2963     DATA k/1.099730,0.418900,0.220939,0.220907,0.418771,1.100674/
2964    
2965 pam-fi 1.18 real xp,yp,zp
2966     real xyzp(3),bxyz(3)
2967     equivalence (xp,xyzp(1)),(yp,xyzp(2)),(zp,xyzp(3))
2968    
2969 mocchiut 1.1 * =================================================
2970     * new estimate of positions using ETA algorithm
2971     * and
2972     * search for new couples and single clusters to add
2973     * =================================================
2974     call track_init
2975     do ip=1,nplanes !loop on planes
2976    
2977 pam-fi 1.18 xP=XV_STORE(nplanes-ip+1,ibest)
2978     yP=YV_STORE(nplanes-ip+1,ibest)
2979     zP=ZV_STORE(nplanes-ip+1,ibest)
2980     call gufld(xyzp,bxyz)
2981 pam-fi 1.20 BX_STORE(nplanes-ip+1,ibest)=bxyz(1)
2982     BY_STORE(nplanes-ip+1,ibest)=bxyz(2)
2983     c$$$ bxyz(1)=0
2984 pam-fi 1.18 c$$$ bxyz(2)=0
2985     c$$$ bxyz(3)=0
2986 pam-fi 1.11 * |||||||||||||||||||||||||||||||||||||||||||||||||
2987 mocchiut 1.1 * -------------------------------------------------
2988     * If the plane has been already included, it just
2989     * computes again the coordinates of the x-y couple
2990     * using improved PFAs
2991     * -------------------------------------------------
2992 pam-fi 1.11 * |||||||||||||||||||||||||||||||||||||||||||||||||
2993 mocchiut 1.1 if(XGOOD_STORE(nplanes-ip+1,ibest).eq.1..and.
2994     $ YGOOD_STORE(nplanes-ip+1,ibest).eq.1. )then
2995    
2996     id=CP_STORE(nplanes-ip+1,ibest)
2997    
2998     is=is_cp(id)
2999     icp=icp_cp(id)
3000     if(ip_cp(id).ne.ip)
3001     $ print*,'OKKIO!!'
3002     $ ,'id ',id,is,icp
3003     $ ,ip_cp(id),ip
3004     icx=clx(ip,icp)
3005     icy=cly(ip,icp)
3006 pam-fi 1.18 c call xyz_PAM(icx,icy,is,
3007     c $ PFA,PFA,
3008     c $ AXV_STORE(nplanes-ip+1,ibest),
3009     c $ AYV_STORE(nplanes-ip+1,ibest))
3010 mocchiut 1.1 call xyz_PAM(icx,icy,is,
3011     $ PFA,PFA,
3012     $ AXV_STORE(nplanes-ip+1,ibest),
3013 pam-fi 1.18 $ AYV_STORE(nplanes-ip+1,ibest),
3014     $ bxyz(1),
3015     $ bxyz(2)
3016     $ )
3017 pam-fi 1.20
3018 mocchiut 1.1 xm(nplanes-ip+1) = xPAM
3019     ym(nplanes-ip+1) = yPAM
3020     zm(nplanes-ip+1) = zPAM
3021     xgood(nplanes-ip+1) = 1
3022     ygood(nplanes-ip+1) = 1
3023     resx(nplanes-ip+1) = resxPAM
3024     resy(nplanes-ip+1) = resyPAM
3025    
3026 pam-fi 1.20 dedxtrk_x(nplanes-ip+1)=sgnl(icx)/mip(VIEW(icx),LADDER(icx))
3027     dedxtrk_y(nplanes-ip+1)=sgnl(icy)/mip(VIEW(icy),LADDER(icy))
3028 mocchiut 1.1
3029 pam-fi 1.11 * |||||||||||||||||||||||||||||||||||||||||||||||||
3030 mocchiut 1.1 * -------------------------------------------------
3031     * If the plane has NOT been already included,
3032     * it tries to include a COUPLE or a single cluster
3033     * -------------------------------------------------
3034 pam-fi 1.11 * |||||||||||||||||||||||||||||||||||||||||||||||||
3035 mocchiut 1.1 else
3036    
3037     xgood(nplanes-ip+1)=0
3038     ygood(nplanes-ip+1)=0
3039    
3040     * --------------------------------------------------------------
3041     * determine which ladder and sensor are intersected by the track
3042     call whichsensor(ip,xP,yP,nldt,ist)
3043     * if the track hit the plane in a dead area, go to the next plane
3044     if(nldt.eq.0.or.ist.eq.0)goto 133
3045 pam-fi 1.20
3046     SENSOR_STORE(nplanes-ip+1,IBEST)=ist
3047     LADDER_STORE(nplanes-ip+1,IBEST)=nldt
3048 mocchiut 1.1 * --------------------------------------------------------------
3049    
3050     if(DEBUG)then
3051     print*,
3052     $ '------ Plane ',ip,' intersected on LADDER ',nldt
3053     $ ,' SENSOR ',ist
3054     print*,
3055     $ '------ coord: ',XP,YP
3056     endif
3057    
3058     * ===========================================
3059     * STEP 1 >>>>>>> try to include a new couple
3060     * ===========================================
3061     c if(DEBUG)print*,'>>>> try to include a new couple'
3062     distmin=1000000.
3063     xmm = 0.
3064     ymm = 0.
3065     zmm = 0.
3066     rxmm = 0.
3067     rymm = 0.
3068     dedxmmx = 0. !(1)
3069     dedxmmy = 0. !(1)
3070     idm = 0 !ID of the closer couple
3071     distance=0.
3072     do icp=1,ncp_plane(ip) !loop on couples on plane icp
3073     icx=clx(ip,icp)
3074     icy=cly(ip,icp)
3075     if(LADDER(icx).ne.nldt.or. !If the ladder number does not match
3076 pam-fi 1.3 c $ cl_used(icx).eq.1.or. !or the X cluster is already used
3077     c $ cl_used(icy).eq.1.or. !or the Y cluster is already used
3078     $ cl_used(icx).ne.0.or. !or the X cluster is already used !(3)
3079     $ cl_used(icy).ne.0.or. !or the Y cluster is already used !(3)
3080 mocchiut 1.1 $ .false.)goto 1188 !then jump to next couple.
3081     *
3082     call xyz_PAM(icx,icy,ist,
3083     $ PFA,PFA,
3084     $ AXV_STORE(nplanes-ip+1,ibest),
3085 pam-fi 1.18 $ AYV_STORE(nplanes-ip+1,ibest),
3086     $ bxyz(1),
3087     $ bxyz(2)
3088     $ )
3089 mocchiut 1.1
3090     distance = distance_to(XP,YP)
3091 pam-fi 1.20 c distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3092 mocchiut 1.1 id=id_cp(ip,icp,ist)
3093     if(DEBUG)print*,'( couple ',id
3094 pam-fi 1.20 $ ,' ) distance ',distance
3095 mocchiut 1.1 if(distance.lt.distmin)then
3096     xmm = xPAM
3097     ymm = yPAM
3098     zmm = zPAM
3099     rxmm = resxPAM
3100     rymm = resyPAM
3101     distmin = distance
3102     idm = id
3103 pam-fi 1.18 dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3104     dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3105 pam-fi 1.20 c QUIQUI --> non devo moltiplicare per clinc?!?!?!
3106     clincnewc=10*sqrt(rymm**2+rxmm**2 !QUIQUI
3107     $ +RCHI2_STORE(ibest)*k(ip)*(cov(1,1)+cov(2,2))) !QUIQUI
3108 mocchiut 1.1 endif
3109     1188 continue
3110     enddo !end loop on couples on plane icp
3111 pam-fi 1.20 c if(distmin.le.clinc)then !QUIQUI
3112     if(distmin.le.clincnewc)then !QUIQUI
3113 mocchiut 1.1 * -----------------------------------
3114 pam-fi 1.20 xm(nplanes-ip+1) = xmm !<<<
3115     ym(nplanes-ip+1) = ymm !<<<
3116     zm(nplanes-ip+1) = zmm !<<<
3117     xgood(nplanes-ip+1) = 1 !<<<
3118     ygood(nplanes-ip+1) = 1 !<<<
3119     resx(nplanes-ip+1)=rxmm !<<<
3120     resy(nplanes-ip+1)=rymm !<<<
3121     dedxtrk_x(nplanes-ip+1) = dedxmmx !<<<
3122     dedxtrk_y(nplanes-ip+1) = dedxmmy !<<<
3123 mocchiut 1.1 * -----------------------------------
3124     CP_STORE(nplanes-ip+1,ibest)=idm
3125     if(DEBUG)print*,'%%%% included couple ',idm
3126 pam-fi 1.20 $ ,' (dist.= ',distmin,', cut ',clinc,' )'
3127 mocchiut 1.1 goto 133 !next plane
3128     endif
3129     * ================================================
3130     * STEP 2 >>>>>>> try to include a single cluster
3131     * either from a couple or single
3132     * ================================================
3133     c if(DEBUG)print*,'>>>> try to include a new cluster'
3134     distmin=1000000.
3135     xmm_A = 0. !---------------------------
3136     ymm_A = 0. ! init variables that
3137     zmm_A = 0. ! define the SINGLET
3138     xmm_B = 0. !
3139     ymm_B = 0. !
3140     zmm_B = 0. !
3141     rxmm = 0. !
3142     rymm = 0. !
3143     dedxmmx = 0. !(1)
3144     dedxmmy = 0. !(1)
3145     iclm=0 !---------------------------
3146     distance=0.
3147    
3148     *----- clusters inside couples -------------------------------------
3149     do icp=1,ncp_plane(ip) !loop on cluster inside couples
3150     icx=clx(ip,icp)
3151     icy=cly(ip,icp)
3152     id=id_cp(ip,icp,ist)
3153     if(LADDER(icx).ne.nldt)goto 11882 !if the ladder number does not match
3154     * !jump to the next couple
3155     *----- try cluster x -----------------------------------------------
3156 pam-fi 1.3 c if(cl_used(icx).eq.1)goto 11881 !if the X cluster is already used
3157     if(cl_used(icx).ne.0)goto 11881 !if the X cluster is already used !(3)
3158 mocchiut 1.1 * !jump to the Y cluster
3159 pam-fi 1.18 c call xyz_PAM(icx,0,ist,
3160     c $ PFA,PFA,
3161     c $ AXV_STORE(nplanes-ip+1,ibest),0.)
3162 mocchiut 1.1 call xyz_PAM(icx,0,ist,
3163     $ PFA,PFA,
3164 pam-fi 1.18 $ AXV_STORE(nplanes-ip+1,ibest),0.,
3165     $ bxyz(1),
3166     $ bxyz(2)
3167     $ )
3168 mocchiut 1.1 distance = distance_to(XP,YP)
3169 pam-fi 1.20 c distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3170 mocchiut 1.1 if(DEBUG)print*,'( cl-X ',icx
3171 pam-fi 1.20 $ ,' in cp ',id,' ) distance ',distance
3172 mocchiut 1.1 if(distance.lt.distmin)then
3173     xmm_A = xPAM_A
3174     ymm_A = yPAM_A
3175     zmm_A = zPAM_A
3176     xmm_B = xPAM_B
3177     ymm_B = yPAM_B
3178     zmm_B = zPAM_B
3179     rxmm = resxPAM
3180     rymm = resyPAM
3181     distmin = distance
3182     iclm = icx
3183 pam-fi 1.18 c dedxmm = sgnl(icx) !(1)
3184     dedxmmx = sgnl(icx)/mip(VIEW(icx),LADDER(icx)) !(1)(2)
3185 mocchiut 1.1 dedxmmy = 0. !(1)
3186     endif
3187     11881 continue
3188     *----- try cluster y -----------------------------------------------
3189 pam-fi 1.3 c if(cl_used(icy).eq.1)goto 11882 !if the Y cluster is already used
3190     if(cl_used(icy).ne.0)goto 11882 !if the Y cluster is already used !(3)
3191 mocchiut 1.1 * !jump to the next couple
3192 pam-fi 1.18 c call xyz_PAM(0,icy,ist,
3193     c $ PFA,PFA,
3194     c $ 0.,AYV_STORE(nplanes-ip+1,ibest))
3195 mocchiut 1.1 call xyz_PAM(0,icy,ist,
3196     $ PFA,PFA,
3197 pam-fi 1.18 $ 0.,AYV_STORE(nplanes-ip+1,ibest),
3198     $ bxyz(1),
3199     $ bxyz(2)
3200     $ )
3201 mocchiut 1.1 distance = distance_to(XP,YP)
3202 pam-fi 1.20 c distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3203 mocchiut 1.1 if(DEBUG)print*,'( cl-Y ',icy
3204 pam-fi 1.20 $ ,' in cp ',id,' ) distance ',distance
3205 mocchiut 1.1 if(distance.lt.distmin)then
3206     xmm_A = xPAM_A
3207     ymm_A = yPAM_A
3208     zmm_A = zPAM_A
3209     xmm_B = xPAM_B
3210     ymm_B = yPAM_B
3211     zmm_B = zPAM_B
3212     rxmm = resxPAM
3213     rymm = resyPAM
3214     distmin = distance
3215     iclm = icy
3216 pam-fi 1.18 c dedxmm = sgnl(icy) !(1)
3217 mocchiut 1.1 dedxmmx = 0. !(1)
3218 pam-fi 1.18 dedxmmy = sgnl(icy)/mip(VIEW(icy),LADDER(icy)) !(1)(2)
3219 mocchiut 1.1 endif
3220     11882 continue
3221     enddo !end loop on cluster inside couples
3222 pam-fi 1.17 *----- single clusters -----------------------------------------------
3223     c print*,'## ncls(',ip,') ',ncls(ip)
3224 mocchiut 1.1 do ic=1,ncls(ip) !loop on single clusters
3225     icl=cls(ip,ic)
3226 pam-fi 1.3 c if(cl_used(icl).eq.1.or. !if the cluster is already used
3227     if(cl_used(icl).ne.0.or. !if the cluster is already used !(3)
3228 mocchiut 1.1 $ LADDER(icl).ne.nldt.or. !or the ladder number does not match
3229     $ .false.)goto 18882 !jump to the next singlet
3230     if(mod(VIEW(icl),2).eq.0)then!<---- X view
3231     call xyz_PAM(icl,0,ist,
3232     $ PFA,PFA,
3233 pam-fi 1.18 $ AXV_STORE(nplanes-ip+1,ibest),0.,
3234     $ bxyz(1),
3235     $ bxyz(2)
3236     $ )
3237 mocchiut 1.1 else !<---- Y view
3238     call xyz_PAM(0,icl,ist,
3239     $ PFA,PFA,
3240 pam-fi 1.18 $ 0.,AYV_STORE(nplanes-ip+1,ibest),
3241     $ bxyz(1),
3242     $ bxyz(2)
3243     $ )
3244 mocchiut 1.1 endif
3245    
3246     distance = distance_to(XP,YP)
3247 pam-fi 1.20 c distance = distance / RCHI2_STORE(ibest)!<<< MS !QUIQUI
3248 mocchiut 1.1 if(DEBUG)print*,'( cl-s ',icl
3249 pam-fi 1.20 $ ,' ) distance ',distance,'<',distmin,' ?'
3250 mocchiut 1.1 if(distance.lt.distmin)then
3251 pam-fi 1.17 if(DEBUG)print*,'YES'
3252 mocchiut 1.1 xmm_A = xPAM_A
3253     ymm_A = yPAM_A
3254     zmm_A = zPAM_A
3255     xmm_B = xPAM_B
3256     ymm_B = yPAM_B
3257     zmm_B = zPAM_B
3258     rxmm = resxPAM
3259     rymm = resyPAM
3260     distmin = distance
3261     iclm = icl
3262     if(mod(VIEW(icl),2).eq.0)then !<---- X view
3263 pam-fi 1.20 dedxmmx = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
3264     dedxmmy = 0.
3265 mocchiut 1.1 else !<---- Y view
3266 pam-fi 1.20 dedxmmx = 0.
3267     dedxmmy = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
3268 mocchiut 1.1 endif
3269     endif
3270     18882 continue
3271     enddo !end loop on single clusters
3272 pam-fi 1.17 c print*,'## distmin ', distmin,' clinc ',clinc
3273 pam-fi 1.20
3274     c QUIQUI------------
3275     c anche qui: non ci vuole clinc???
3276     if(iclm.ne.0)then
3277     if(mod(VIEW(iclm),2).eq.0)then
3278     clincnew=
3279     $ 20*
3280     $ sqrt(rxmm**2+RCHI2_STORE(ibest)*k(ip)*cov(1,1))
3281     else if(mod(VIEW(iclm),2).ne.0)then
3282     clincnew=
3283     $ 10*
3284     $ sqrt(rymm**2+RCHI2_STORE(ibest)*k(ip)*cov(2,2))
3285     endif
3286     c QUIQUI------------
3287 mocchiut 1.1
3288 pam-fi 1.20 if(distmin.le.clincnew)then !QUIQUI
3289     c if(distmin.le.clinc)then !QUIQUI
3290    
3291     CLS_STORE(nplanes-ip+1,ibest)=iclm !<<<<
3292     * ----------------------------
3293     c print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
3294     if(mod(VIEW(iclm),2).eq.0)then
3295     XGOOD(nplanes-ip+1)=1.
3296     resx(nplanes-ip+1)=rxmm
3297     if(DEBUG)print*,'%%%% included X-cl ',iclm
3298     $ ,'( chi^2, ',RCHI2_STORE(ibest)
3299     $ ,', dist.= ',distmin
3300     $ ,', cut ',clinc,' )'
3301     else
3302     YGOOD(nplanes-ip+1)=1.
3303     resy(nplanes-ip+1)=rymm
3304     if(DEBUG)print*,'%%%% included Y-cl ',iclm
3305     $ ,'( chi^2, ',RCHI2_STORE(ibest)
3306     $ ,', dist.= ', distmin
3307     $ ,', cut ',clinc,' )'
3308     endif
3309     c print*,'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
3310     * ----------------------------
3311     xm_A(nplanes-ip+1) = xmm_A
3312     ym_A(nplanes-ip+1) = ymm_A
3313     xm_B(nplanes-ip+1) = xmm_B
3314     ym_B(nplanes-ip+1) = ymm_B
3315     zm(nplanes-ip+1) = (zmm_A+zmm_B)/2.
3316     dedxtrk_x(nplanes-ip+1) = dedxmmx !<<<
3317     dedxtrk_y(nplanes-ip+1) = dedxmmy !<<<
3318     * ----------------------------
3319 mocchiut 1.1 endif
3320     endif
3321     endif
3322     133 continue
3323     enddo !end loop on planes
3324    
3325    
3326    
3327     return
3328     end
3329    
3330     ***************************************************
3331     * *
3332     * *
3333     * *
3334     * *
3335     * *
3336     * *
3337     **************************************************
3338 pam-fi 1.3 *
3339 mocchiut 1.1 subroutine clean_XYclouds(ibest,iflag)
3340    
3341     include 'commontracker.f'
3342 pam-fi 1.9 include 'level1.f'
3343 mocchiut 1.1 include 'common_momanhough.f'
3344 pam-fi 1.20 include 'level2.f'
3345 mocchiut 1.1
3346     do ip=1,nplanes !loop on planes
3347    
3348     id=CP_STORE(nplanes-ip+1,ibest)
3349     icl=CLS_STORE(nplanes-ip+1,ibest)
3350     if(id.ne.0.or.icl.ne.0)then
3351     if(id.ne.0)then
3352     iclx=clx(ip,icp_cp(id))
3353     icly=cly(ip,icp_cp(id))
3354 pam-fi 1.20 cl_used(iclx)=ntrk !tag used clusters
3355     cl_used(icly)=ntrk !tag used clusters
3356 mocchiut 1.1 elseif(icl.ne.0)then
3357 pam-fi 1.20 cl_used(icl)=ntrk !tag used clusters
3358 mocchiut 1.1 endif
3359    
3360     * -----------------------------
3361     * remove the couple from clouds
3362     * remove also vitual couples containing the
3363     * selected clusters
3364     * -----------------------------
3365     do icp=1,ncp_plane(ip)
3366     if(
3367     $ clx(ip,icp).eq.iclx
3368     $ .or.
3369     $ clx(ip,icp).eq.icl
3370     $ .or.
3371     $ cly(ip,icp).eq.icly
3372     $ .or.
3373     $ cly(ip,icp).eq.icl
3374     $ )then
3375     id=id_cp(ip,icp,1)
3376     if(DEBUG)then
3377     print*,ip,' <<< cp ',id
3378     $ ,' ( cl-x '
3379     $ ,clx(ip,icp)
3380     $ ,' cl-y '
3381     $ ,cly(ip,icp),' ) --> removed'
3382     endif
3383     * -----------------------------
3384     * remove the couple from clouds
3385     do iyz=1,nclouds_yz
3386     if(cpcloud_yz(iyz,abs(id)).ne.0)then
3387     ptcloud_yz(iyz)=ptcloud_yz(iyz)-1
3388     cpcloud_yz(iyz,abs(id))=0
3389     endif
3390     enddo
3391     do ixz=1,nclouds_xz
3392     if(cpcloud_xz(ixz,abs(id)).ne.0)then
3393     ptcloud_xz(ixz)=ptcloud_xz(ixz)-1
3394     cpcloud_xz(ixz,abs(id))=0
3395     endif
3396     enddo
3397     * -----------------------------
3398     endif
3399     enddo
3400    
3401     endif
3402     enddo !end loop on planes
3403    
3404     return
3405     end
3406    
3407    
3408    
3409    
3410    
3411    
3412     * ****************************************************
3413    
3414     subroutine init_level2
3415    
3416     include 'commontracker.f'
3417 pam-fi 1.9 include 'level1.f'
3418 mocchiut 1.1 include 'common_momanhough.f'
3419     include 'level2.f'
3420    
3421 pam-fi 1.20 * ---------------------------------
3422     * variables initialized from level1
3423     * ---------------------------------
3424 pam-fi 1.4 do i=1,nviews
3425     good2(i)=good1(i)
3426 pam-fi 1.20 do j=1,nva1_view
3427     vkflag(i,j)=1
3428     if(cnnev(i,j).le.0)then
3429     vkflag(i,j)=cnnev(i,j)
3430     endif
3431     enddo
3432 pam-fi 1.4 enddo
3433 pam-fi 1.20 * ----------------
3434     * level2 variables
3435     * ----------------
3436 mocchiut 1.1 NTRK = 0
3437 pam-fi 1.9 do it=1,NTRKMAX
3438 mocchiut 1.1 IMAGE(IT)=0
3439     CHI2_nt(IT) = -100000.
3440     do ip=1,nplanes
3441     XM_nt(IP,IT) = 0
3442     YM_nt(IP,IT) = 0
3443     ZM_nt(IP,IT) = 0
3444     RESX_nt(IP,IT) = 0
3445     RESY_nt(IP,IT) = 0
3446 pam-fi 1.20 TAILX_nt(IP,IT) = 0
3447     TAILY_nt(IP,IT) = 0
3448     XBAD(IP,IT) = 0
3449     YBAD(IP,IT) = 0
3450 mocchiut 1.1 XGOOD_nt(IP,IT) = 0
3451     YGOOD_nt(IP,IT) = 0
3452 pam-fi 1.20 LS(IP,IT) = 0
3453 mocchiut 1.1 DEDX_X(IP,IT) = 0
3454     DEDX_Y(IP,IT) = 0
3455 pam-fi 1.3 CLTRX(IP,IT) = 0
3456     CLTRY(IP,IT) = 0
3457 mocchiut 1.1 enddo
3458     do ipa=1,5
3459     AL_nt(IPA,IT) = 0
3460     do ipaa=1,5
3461     coval(ipa,ipaa,IT)=0
3462     enddo
3463     enddo
3464     enddo
3465     nclsx=0
3466     nclsy=0
3467     do ip=1,NSINGMAX
3468     planex(ip)=0
3469     xs(1,ip)=0
3470     xs(2,ip)=0
3471     sgnlxs(ip)=0
3472     planey(ip)=0
3473     ys(1,ip)=0
3474     ys(2,ip)=0
3475     sgnlys(ip)=0
3476     enddo
3477     end
3478    
3479    
3480     ************************************************************
3481     *
3482     *
3483     *
3484     *
3485     *
3486     *
3487     *
3488     ************************************************************
3489    
3490    
3491 pam-fi 1.9 subroutine init_hough
3492    
3493     include 'commontracker.f'
3494     include 'level1.f'
3495     include 'common_momanhough.f'
3496     include 'common_hough.f'
3497     include 'level2.f'
3498    
3499     ntrpt_nt=0
3500     ndblt_nt=0
3501     NCLOUDS_XZ_nt=0
3502     NCLOUDS_YZ_nt=0
3503     do idb=1,ndblt_max_nt
3504     db_cloud_nt(idb)=0
3505     alfayz1_nt(idb)=0
3506     alfayz2_nt(idb)=0
3507     enddo
3508 pam-fi 1.14 do itr=1,ntrpt_max_nt
3509 pam-fi 1.9 tr_cloud_nt(itr)=0
3510     alfaxz1_nt(itr)=0
3511     alfaxz2_nt(itr)=0
3512     alfaxz3_nt(itr)=0
3513     enddo
3514     do idb=1,ncloyz_max
3515     ptcloud_yz_nt(idb)=0
3516     alfayz1_av_nt(idb)=0
3517     alfayz2_av_nt(idb)=0
3518     enddo
3519     do itr=1,ncloxz_max
3520     ptcloud_xz_nt(itr)=0
3521     alfaxz1_av_nt(itr)=0
3522     alfaxz2_av_nt(itr)=0
3523     alfaxz3_av_nt(itr)=0
3524     enddo
3525    
3526     ntrpt=0
3527     ndblt=0
3528     NCLOUDS_XZ=0
3529     NCLOUDS_YZ=0
3530     do idb=1,ndblt_max
3531     db_cloud(idb)=0
3532     cpyz1(idb)=0
3533     cpyz2(idb)=0
3534     alfayz1(idb)=0
3535     alfayz2(idb)=0
3536     enddo
3537 pam-fi 1.14 do itr=1,ntrpt_max
3538 pam-fi 1.9 tr_cloud(itr)=0
3539     cpxz1(itr)=0
3540     cpxz2(itr)=0
3541     cpxz3(itr)=0
3542     alfaxz1(itr)=0
3543     alfaxz2(itr)=0
3544     alfaxz3(itr)=0
3545     enddo
3546     do idb=1,ncloyz_max
3547     ptcloud_yz(idb)=0
3548     alfayz1_av(idb)=0
3549     alfayz2_av(idb)=0
3550     do idbb=1,ncouplemaxtot
3551     cpcloud_yz(idb,idbb)=0
3552     enddo
3553     enddo
3554     do itr=1,ncloxz_max
3555     ptcloud_xz(itr)=0
3556     alfaxz1_av(itr)=0
3557     alfaxz2_av(itr)=0
3558     alfaxz3_av(itr)=0
3559     do itrr=1,ncouplemaxtot
3560     cpcloud_xz(itr,itrr)=0
3561     enddo
3562     enddo
3563     end
3564     ************************************************************
3565     *
3566     *
3567     *
3568     *
3569     *
3570     *
3571     *
3572     ************************************************************
3573    
3574    
3575 mocchiut 1.1 subroutine fill_level2_tracks(ntr)
3576    
3577     * -------------------------------------------------------
3578     * This routine fills the ntr-th element of the variables
3579     * inside the level2_tracks common, which correspond
3580     * to the ntr-th track info.
3581     * -------------------------------------------------------
3582    
3583    
3584     include 'commontracker.f'
3585 pam-fi 1.3 include 'level1.f'
3586 pam-fi 1.9 include 'common_momanhough.f'
3587 mocchiut 1.1 include 'level2.f'
3588     include 'common_mini_2.f'
3589 pam-fi 1.20 include 'calib.f'
3590    
3591     character*10 PFA
3592     common/FINALPFA/PFA
3593    
3594     real sinth,phi,pig
3595     integer ssensor,sladder
3596 mocchiut 1.1 pig=acos(-1.)
3597    
3598 pam-fi 1.20 * -------------------------------------
3599 mocchiut 1.1 chi2_nt(ntr) = sngl(chi2)
3600 pam-fi 1.8 nstep_nt(ntr) = nstep
3601 pam-fi 1.20 * -------------------------------------
3602 pam-fi 1.9 phi = al(4)
3603     sinth = al(3)
3604     if(sinth.lt.0)then
3605     sinth = -sinth
3606     phi = phi + pig
3607     endif
3608     npig = aint(phi/(2*pig))
3609     phi = phi - npig*2*pig
3610     if(phi.lt.0)
3611     $ phi = phi + 2*pig
3612     al(4) = phi
3613     al(3) = sinth
3614 mocchiut 1.1 do i=1,5
3615     al_nt(i,ntr) = sngl(al(i))
3616     do j=1,5
3617     coval(i,j,ntr) = sngl(cov(i,j))
3618     enddo
3619     enddo
3620 pam-fi 1.20 * -------------------------------------
3621 mocchiut 1.1 do ip=1,nplanes ! loop on planes
3622     xgood_nt(ip,ntr) = int(xgood(ip))
3623     ygood_nt(ip,ntr) = int(ygood(ip))
3624     xm_nt(ip,ntr) = sngl(xm(ip))
3625     ym_nt(ip,ntr) = sngl(ym(ip))
3626     zm_nt(ip,ntr) = sngl(zm(ip))
3627     RESX_nt(IP,ntr) = sngl(resx(ip))
3628     RESY_nt(IP,ntr) = sngl(resy(ip))
3629 pam-fi 1.20 TAILX_nt(IP,ntr) = 0.
3630     TAILY_nt(IP,ntr) = 0.
3631 mocchiut 1.1 xv_nt(ip,ntr) = sngl(xv(ip))
3632     yv_nt(ip,ntr) = sngl(yv(ip))
3633     zv_nt(ip,ntr) = sngl(zv(ip))
3634     axv_nt(ip,ntr) = sngl(axv(ip))
3635 pam-fi 1.18 ayv_nt(ip,ntr) = sngl(ayv(ip))
3636     c l'avevo dimenticato!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3637     factor = sqrt(
3638 pam-fi 1.19 $ tan( acos(-1.) * sngl(axv(ip)) /180. )**2 +
3639     $ tan( acos(-1.) * sngl(ayv(ip)) /180. )**2 +
3640 pam-fi 1.18 $ 1. )
3641     c !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3642     dedx_x(ip,ntr) = sngl(dedxtrk_x(ip)/factor)
3643     dedx_y(ip,ntr) = sngl(dedxtrk_y(ip)/factor)
3644 pam-fi 1.3
3645 pam-fi 1.20 ax = axv_nt(ip,ntr)
3646     ay = ayv_nt(ip,ntr)
3647     bfx = BX_STORE(ip,IDCAND)
3648     bfy = BY_STORE(ip,IDCAND)
3649     if(ip.eq.6) ax = -1. * axv_nt(ip,ntr)
3650     if(ip.eq.6) bfy = -1. * BY_STORE(ip,IDCAND)
3651     tgtemp = tan(ax*acos(-1.)/180.) + pmuH_h*bfy*0.00001
3652     angx = 180.*atan(tgtemp)/acos(-1.)
3653     tgtemp = tan(ay*acos(-1.)/180.)+pmuH_e*bfx*0.00001
3654     angy = 180.*atan(tgtemp)/acos(-1.)
3655    
3656     c print*,'* ',ip,bfx,bfy,angx,angy
3657    
3658     id = CP_STORE(ip,IDCAND) ! couple id
3659 pam-fi 1.3 icl = CLS_STORE(ip,IDCAND)
3660 pam-fi 1.20 ssensor = -1
3661     sladder = -1
3662     ssensor = SENSOR_STORE(ip,IDCAND)
3663     sladder = LADDER_STORE(ip,IDCAND)
3664     if(ip.eq.6.and.ssensor.ne.0)ssensor = 3 - ssensor !notazione paolo x align
3665     LS(IP,ntr) = ssensor+10*sladder
3666    
3667 pam-fi 1.3 if(id.ne.0)then
3668 pam-fi 1.20 c >>> is a couple
3669 pam-fi 1.3 cltrx(ip,ntr) = clx(nplanes-ip+1,icp_cp(id))
3670     cltry(ip,ntr) = cly(nplanes-ip+1,icp_cp(id))
3671 pam-fi 1.20
3672     c$$$ if(is_cp(id).ne.ssensor)
3673     c$$$ $ print*,'ERROR is sensor assignment (couple)'
3674     c$$$ $ ,is_cp(id),ssensor
3675     c$$$ if(LADDER(clx(nplanes-ip+1,icp_cp(id))).ne.sladder)
3676     c$$$ $ print*,'ERROR is ladder assignment (couple)'
3677     c$$$ $ ,LADDER(clx(nplanes-ip+1,icp_cp(id))),sladder
3678    
3679     nnnnx = npfastrips(clx(nplanes-ip+1,icp_cp(id)),PFA,angx)
3680     nnnny = npfastrips(cly(nplanes-ip+1,icp_cp(id)),PFA,angy)
3681     xbad(ip,ntr)= nbadstrips(nnnnx,clx(nplanes-ip+1,icp_cp(id)))
3682     ybad(ip,ntr)= nbadstrips(nnnny,cly(nplanes-ip+1,icp_cp(id)))
3683    
3684     if(nsatstrips(clx(nplanes-ip+1,icp_cp(id))).gt.0)
3685     $ dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3686     if(nsatstrips(cly(nplanes-ip+1,icp_cp(id))).gt.0)
3687     $ dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3688    
3689 pam-fi 1.3 elseif(icl.ne.0)then
3690 pam-fi 1.20 c >>> is a singlet
3691     c$$$ if(LADDER(icl).ne.sladder)
3692     c$$$ $ print*,'ERROR is ladder assignment (single)'
3693     c$$$ $ ,LADDER(icl),sladder
3694     if(mod(VIEW(icl),2).eq.0)then
3695     cltrx(ip,ntr)=icl
3696     nnnnn = npfastrips(icl,PFA,angx)
3697     xbad(ip,ntr) = nbadstrips(nnnnn,icl)
3698     if(nsatstrips(icl).gt.0)dedx_x(ip,ntr)=-dedx_x(ip,ntr)
3699     elseif(mod(VIEW(icl),2).eq.1)then
3700     cltry(ip,ntr)=icl
3701     nnnnn = npfastrips(icl,PFA,angy)
3702     ybad(ip,ntr) = nbadstrips(nnnnn,icl)
3703     if(nsatstrips(icl).gt.0)dedx_y(ip,ntr)=-dedx_y(ip,ntr)
3704     endif
3705 pam-fi 1.3 endif
3706    
3707 mocchiut 1.1 enddo
3708    
3709    
3710 pam-fi 1.20 c$$$ print*,(xgood(i),i=1,6)
3711     c$$$ print*,(ygood(i),i=1,6)
3712     c$$$ print*,(ls(i,ntr),i=1,6)
3713     c$$$ print*,(dedx_x(i,ntr),i=1,6)
3714     c$$$ print*,(dedx_y(i,ntr),i=1,6)
3715     c$$$ print*,'-----------------------'
3716    
3717 mocchiut 1.1 end
3718    
3719     subroutine fill_level2_siglets
3720    
3721     * -------------------------------------------------------
3722     * This routine fills the elements of the variables
3723     * inside the level2_singletsx and level2_singletsy commons,
3724     * which store info on clusters outside the tracks
3725     * -------------------------------------------------------
3726    
3727     include 'commontracker.f'
3728 pam-fi 1.9 include 'calib.f'
3729 mocchiut 1.1 include 'level1.f'
3730 pam-fi 1.9 include 'common_momanhough.f'
3731 mocchiut 1.1 include 'level2.f'
3732     include 'common_xyzPAM.f'
3733    
3734     * count #cluster per plane not associated to any track
3735     nclsx = 0
3736     nclsy = 0
3737    
3738 pam-fi 1.9 do iv = 1,nviews
3739     if( mask_view(iv).ne.0 )good2(iv) = 20+mask_view(iv)
3740     enddo
3741    
3742 mocchiut 1.1 do icl=1,nclstr1
3743     if(cl_used(icl).eq.0)then !cluster not included in any track
3744     ip=nplanes-npl(VIEW(icl))+1
3745     if(mod(VIEW(icl),2).eq.0)then !=== X views
3746     nclsx = nclsx + 1
3747     planex(nclsx) = ip
3748 pam-fi 1.20 sgnlxs(nclsx) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
3749     if(nsatstrips(icl).gt.0)sgnlxs(nclsx)=-sgnlxs(nclsx)
3750 pam-fi 1.3 clsx(nclsx) = icl
3751 mocchiut 1.1 do is=1,2
3752     c call xyz_PAM(icl,0,is,'COG1',' ',0.,0.)
3753 pam-fi 1.18 c call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.)
3754     call xyz_PAM(icl,0,is,PFAdef,' ',0.,0.,0.,0.)
3755 mocchiut 1.1 xs(is,nclsx) = (xPAM_A+xPAM_B)/2
3756     enddo
3757     c$$$ print*,'nclsx ',nclsx
3758     c$$$ print*,'planex(nclsx) ',planex(nclsx)
3759     c$$$ print*,'sgnlxs(nclsx) ',sgnlxs(nclsx)
3760     c$$$ print*,'xs(1,nclsx) ',xs(1,nclsx)
3761     c$$$ print*,'xs(2,nclsx) ',xs(2,nclsx)
3762     else !=== Y views
3763     nclsy = nclsy + 1
3764     planey(nclsy) = ip
3765 pam-fi 1.20 sgnlys(nclsy) = sgnl(icl)/mip(VIEW(icl),LADDER(icl))
3766     if(nsatstrips(icl).gt.0)sgnlys(nclsy)=-sgnlys(nclsy)
3767 pam-fi 1.3 clsy(nclsy) = icl
3768 mocchiut 1.1 do is=1,2
3769     c call xyz_PAM(0,icl,is,' ','COG1',0.,0.)
3770 pam-fi 1.18 c call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.)
3771     call xyz_PAM(0,icl,is,' ',PFAdef,0.,0.,0.,0.)
3772 mocchiut 1.1 ys(is,nclsy) = (yPAM_A+yPAM_B)/2
3773     enddo
3774     c$$$ print*,'nclsy ',nclsy
3775     c$$$ print*,'planey(nclsy) ',planey(nclsy)
3776     c$$$ print*,'sgnlys(nclsy) ',sgnlys(nclsy)
3777     c$$$ print*,'ys(1,nclsy) ',ys(1,nclsy)
3778     c$$$ print*,'ys(2,nclsy) ',ys(2,nclsy)
3779     endif
3780     endif
3781 pam-fi 1.3
3782     ***** LO METTO QUI PERCHE` NON SO DOVE METTERLO
3783     whichtrack(icl) = cl_used(icl)
3784    
3785 mocchiut 1.1 enddo
3786     end
3787    
3788 pam-fi 1.9 ***************************************************
3789     * *
3790     * *
3791     * *
3792     * *
3793     * *
3794     * *
3795     **************************************************
3796 mocchiut 1.1
3797 pam-fi 1.9 subroutine fill_hough
3798 mocchiut 1.1
3799 pam-fi 1.9 * -------------------------------------------------------
3800     * This routine fills the variables related to the hough
3801     * transform, for the debig n-tuple
3802     * -------------------------------------------------------
3803 mocchiut 1.1
3804 pam-fi 1.9 include 'commontracker.f'
3805     include 'level1.f'
3806     include 'common_momanhough.f'
3807     include 'common_hough.f'
3808     include 'level2.f'
3809 mocchiut 1.1
3810 pam-fi 1.9 if(.false.
3811     $ .or.ntrpt.gt.ntrpt_max_nt
3812     $ .or.ndblt.gt.ndblt_max_nt
3813     $ .or.NCLOUDS_XZ.gt.ncloxz_max
3814     $ .or.NCLOUDS_yZ.gt.ncloyz_max
3815     $ )then
3816     ntrpt_nt=0
3817     ndblt_nt=0
3818     NCLOUDS_XZ_nt=0
3819     NCLOUDS_YZ_nt=0
3820     else
3821     ndblt_nt=ndblt
3822     ntrpt_nt=ntrpt
3823     if(ndblt.ne.0)then
3824     do id=1,ndblt
3825     alfayz1_nt(id)=alfayz1(id) !Y0
3826     alfayz2_nt(id)=alfayz2(id) !tg theta-yz
3827     enddo
3828     endif
3829     if(ndblt.ne.0)then
3830     do it=1,ntrpt
3831     alfaxz1_nt(it)=alfaxz1(it) !X0
3832     alfaxz2_nt(it)=alfaxz2(it) !tg theta-xz
3833     alfaxz3_nt(it)=alfaxz3(it) !1/r
3834     enddo
3835     endif
3836     nclouds_yz_nt=nclouds_yz
3837     nclouds_xz_nt=nclouds_xz
3838     if(nclouds_yz.ne.0)then
3839     nnn=0
3840     do iyz=1,nclouds_yz
3841     ptcloud_yz_nt(iyz)=ptcloud_yz(iyz)
3842     alfayz1_av_nt(iyz)=alfayz1_av(iyz)
3843     alfayz2_av_nt(iyz)=alfayz2_av(iyz)
3844     nnn=nnn+ptcloud_yz(iyz)
3845     enddo
3846     do ipt=1,nnn
3847     db_cloud_nt(ipt)=db_cloud(ipt)
3848     enddo
3849     endif
3850     if(nclouds_xz.ne.0)then
3851     nnn=0
3852     do ixz=1,nclouds_xz
3853     ptcloud_xz_nt(ixz)=ptcloud_xz(ixz)
3854     alfaxz1_av_nt(ixz)=alfaxz1_av(ixz)
3855     alfaxz2_av_nt(ixz)=alfaxz2_av(ixz)
3856     alfaxz3_av_nt(ixz)=alfaxz3_av(ixz)
3857     nnn=nnn+ptcloud_xz(ixz)
3858     enddo
3859     do ipt=1,nnn
3860     tr_cloud_nt(ipt)=tr_cloud(ipt)
3861     enddo
3862     endif
3863     endif
3864     end
3865    

  ViewVC Help
Powered by ViewVC 1.1.23