/[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.3 - (hide annotations) (download)
Tue Sep 5 12:52:20 2006 UTC (18 years, 3 months ago) by pam-fi
Branch: MAIN
CVS Tags: v2r00BETA
Changes since 1.2: +49 -12 lines
implemented class TrkLevel1

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

  ViewVC Help
Powered by ViewVC 1.1.23