/[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.20 - (hide annotations) (download)
Fri Apr 27 10:39:58 2007 UTC (17 years, 7 months ago) by pam-fi
Branch: MAIN
Changes since 1.19: +412 -224 lines
v3r00: new hough parameters, new variables, and other things...

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

  ViewVC Help
Powered by ViewVC 1.1.23