/[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.1 - (hide annotations) (download)
Fri May 19 13:15:54 2006 UTC (18 years, 6 months ago) by mocchiut
Branch: MAIN
Branch point for: DarthVader
Initial revision

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

  ViewVC Help
Powered by ViewVC 1.1.23