/[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.22 - (hide annotations) (download)
Wed May 9 07:50:58 2007 UTC (17 years, 7 months ago) by pam-fi
Branch: MAIN
Changes since 1.21: +12 -2 lines
fixed bug in coordinate shift due to magnetic field

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

  ViewVC Help
Powered by ViewVC 1.1.23