/[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.27 - (hide annotations) (download)
Fri Aug 17 14:36:05 2007 UTC (17 years, 4 months ago) by pam-fi
Branch: MAIN
Changes since 1.26: +30 -14 lines
mplemented Landi correction

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

  ViewVC Help
Powered by ViewVC 1.1.23