/[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.21 - (hide annotations) (download)
Fri Apr 27 12:11:02 2007 UTC (17 years, 7 months ago) by mocchiut
Branch: MAIN
CVS Tags: v3r04, v3r03
Changes since 1.20: +36 -27 lines
Comments commented

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

  ViewVC Help
Powered by ViewVC 1.1.23